GCC Code Coverage Report
Directory: . Exec Total Coverage
File: chainLinkMod.f90 Lines: 58 58 100.0 %
Date: 2015-06-13 Branches: 36 44 81.8 %

Line Exec Source
1
    MODULE chainlinkmod
2
! .. Use Statements ..
3
      USE set_precision, ONLY: wp
4
! ..
5
    CONTAINS
6
7
! Corrected and restructured version in Fortran 90 of
8
! the original Algol 60 routines previously published as
9
!
10
! The argument lists of inlist and outlist could be simplified
11
! further if arguments like m and n were retrieved from the
12
! array sizes of the other arguments.
13
!
14
! ALGORITHM 100
15
! ADD ITEM TO CHAIN-LINKED LIST
16
! and
17
! ALGORITHM 101
18
! REMOVE ITEM FROM CHAIN-LINKED LIST
19
! by
20
! PHILIP J. KIVIAT
21
! United States Steel Corp., Appl. Research Lab., Monroeville,
22
! Penn. ;
23
101
      SUBROUTINE inlist(t, info, m, list, n, first, flag, addr, listfull)
24
! .. Scalar Arguments ..
25
        INTEGER, INTENT (INOUT) :: first
26
        INTEGER, INTENT (IN) :: flag, m, n, t
27
        LOGICAL, INTENT (INOUT) :: listfull
28
! ..
29
! .. Array Arguments ..
30
        INTEGER, INTENT (INOUT) :: addr(:), list(:, :)
31
        INTEGER, INTENT (IN) :: info(:)
32
! ..
33
! .. Local Scalars ..
34
        INTEGER :: i, j, k, link1, link2
35
! ..
36
! inlist adds the information pair {t,info} to the chain-
37
! link structured matrix list (i,j), where t is an order key >= 0, and
38
! info(k) an information vector associated with t. info(k) has
39
! dimension m, list(i,j) has dimensions (n, (m+3)). flag denotes
40
! the head and tail of list(i,j), and first contains the address of
41
! the first (lowest order) entry in list(i,j). addr(k) is a vector
42
! containing the addresses of available (empty) rows in list(i,j).
43
! Initialization: list(i,m+2) = flag, for some i <= n. If list(i,j) is
44
! filled the logical variable listfull returns TRUE.
45
101
        listfull = .FALSE.
46
202
        IF (addr(1)==0) THEN
47
1
          listfull = .TRUE.
48
100
        ELSE IF (addr(n)/=0) THEN
49
! Insertion into an empty list.
50
2
          i = flag
51
2
          link1 = m + 3
52
2
          link2 = m + 2
53
2
          CALL addlink
54
2
          CALL adddata
55
56
        ELSE
57
58
! There is at least one element to compare against.
59
98
          i = first
60
1103
loop:     DO
61
62
1201
            IF (list(i,1)<=t) THEN
63
! Insert after first item
64
1192
              link1 = m + 2
65
1192
              link2 = m + 3
66
            ELSE
67
! Insert before first item
68
9
              link1 = m + 3
69
9
              link2 = m + 2
70
            END IF
71
72
1201
            IF (list(i,link2)/=flag) THEN
73
! Check the next element for the insertion point.
74
1187
              k = i
75
1187
              i = list(i, link2)
76
! Insertion point found.
77
! Continue the search.
78
1187
              IF (list(i,1)>t) THEN
79
84
                j = addr(1)
80
84
                list(j, link1) = list(i, link1)
81
84
                list(k, link2) = addr(1)
82
84
                list(i, link1) = list(k, link2)
83
84
                list(j, link2) = i
84
84
                CALL adddata
85
84
                EXIT loop
86
              ELSE
87
1103
                CYCLE loop
88
              END IF
89
            ELSE
90
! Insert 'after' i (depending on search direction).
91
! Link i into the new element.
92
14
              list(i, link2) = addr(1)
93
            END IF
94
14
            CALL addlink
95
14
            CALL adddata
96
14
            EXIT loop
97
          END DO loop
98
        END IF
99
100
      CONTAINS
101
! These two small routines just remove the need to duplicate
102
! code or have labels and gotos as with the original Algol
103
16
        SUBROUTINE addlink
104
! Insert at one of the ends of the list,
105
! linking to element i in the opposite direction.
106
! As a special case, i .EQ. flag when inserting into the empty list.
107
16
          j = addr(1)
108
16
          list(j, link1) = i
109
16
          list(j, link2) = flag
110
16
          IF (link2==(m+2)) THEN
111
11
            first = addr(1)
112
          END IF
113
16
        END SUBROUTINE addlink
114
115
100
        SUBROUTINE adddata
116
117
100
          list(j, 1) = t
118
100
          list(j, 2:m+1) = info(1:m)
119
100
          addr(1:n) = [ addr(2:n), 0 ]
120
100
        END SUBROUTINE adddata
121
122
      END SUBROUTINE inlist
123
124
50
      SUBROUTINE outlist(vector, m, list, n, first, flag, addr)
125
! outlist removes the first entry (information pair with
126
! lowest order key) from list(i,j) and puts it in vector(k);
127
        INTEGER, INTENT (INOUT) :: first
128
        INTEGER, INTENT (IN) :: flag, m, n
129
! ..
130
! .. Array Arguments ..
131
        INTEGER, INTENT (INOUT) :: addr(:), list(:, :), vector(:)
132
! ..
133
! .. Local Scalars ..
134
        INTEGER :: i
135
! ..
136
! Copy the key and data.
137
50
        vector(1:m+1) = list(first, 1:m+1)
138
139
! Release the first entry.
140
50
        i = n
141
2598
        DO WHILE (addr(i)==0 .AND. i>1)
142
1274
          i = i - 1
143
        END DO
144
50
        IF (addr(i)==0) THEN
145
1
          addr(i) = first
146
        ELSE
147
49
          addr(i+1) = first
148
        END IF
149
50
        IF (list(first,m+3)==flag) THEN
150
! The list is now empty.
151
1
          list(1, m+2) = flag
152
        ELSE
153
49
          first = list(first, m+3)
154
49
          list(first, m+2) = flag
155
        END IF
156
50
      END SUBROUTINE outlist
157
    END MODULE chainlinkmod