Line | Branch | Exec | Source |
---|---|---|---|
1 | module raffle__misc | ||
2 | !! Module contains various miscellaneous functions and subroutines. | ||
3 | use raffle__constants, only: real32 | ||
4 | use raffle__io_utils, only: stop_program | ||
5 | implicit none | ||
6 | |||
7 | |||
8 | private | ||
9 | |||
10 | public :: sort1D, sort2D, sort_str, sort_str_order | ||
11 | public :: set, swap | ||
12 | public :: shuffle | ||
13 | public :: icount, grep, flagmaker | ||
14 | public :: jump, file_check, touch, to_upper, to_lower | ||
15 | public :: strip_null | ||
16 | |||
17 | |||
18 | interface sort1D | ||
19 | !! Sort a 1D array from min to max. | ||
20 | procedure isort1D,rsort1D | ||
21 | end interface sort1D | ||
22 | |||
23 | interface sort2D | ||
24 | !! Sort a 2D array from min to max along the first column. | ||
25 | procedure isort2D,rsort2D | ||
26 | end interface sort2D | ||
27 | |||
28 | interface set | ||
29 | !! Reduce an array to its unique elements. | ||
30 | procedure iset,rset, cset | ||
31 | end interface set | ||
32 | |||
33 | interface swap | ||
34 | !! Swap two elements. | ||
35 | procedure iswap, rswap, rswap_vec, cswap | ||
36 | end interface swap | ||
37 | |||
38 | interface shuffle | ||
39 | !! Shuffle an array. | ||
40 | procedure ishuffle, rshuffle | ||
41 | end interface shuffle | ||
42 | |||
43 | |||
44 | |||
45 | contains | ||
46 | |||
47 | !############################################################################### | ||
48 |
1/2✓ Branch 0 taken 156 times.
✗ Branch 1 not taken.
|
156 | subroutine sort_str(list, lcase) |
49 | !! Sort a list of strings. | ||
50 | implicit none | ||
51 | |||
52 | ! Arguments | ||
53 | character(*), dimension(:), intent(inout) :: list | ||
54 | !! List of strings to be sorted. | ||
55 | logical, optional, intent(in) :: lcase | ||
56 | !! Optional. Boolean whether case insensitive sorting is required. | ||
57 | !! Default is .false. | ||
58 | |||
59 | ! Local variables | ||
60 | integer :: i,loc | ||
61 | !! Loop index. | ||
62 | integer :: charlen | ||
63 | !! Length of the strings. | ||
64 | logical :: lcase_ | ||
65 | !! Boolean whether case insensitive sorting is required. | ||
66 | 156 | character(:), allocatable, dimension(:) :: tlist | |
67 | !! Temporary list for case insensitive sorting. | ||
68 | |||
69 | 156 | charlen = len(list(1)) | |
70 |
2/2✓ Branch 0 taken 60 times.
✓ Branch 1 taken 96 times.
|
156 | if(present(lcase))then |
71 | 60 | lcase_ = lcase | |
72 | else | ||
73 | 96 | lcase_ = .false. | |
74 | end if | ||
75 |
2/2✓ Branch 0 taken 2 times.
✓ Branch 1 taken 154 times.
|
156 | if(lcase_)then |
76 |
8/16✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 2 times.
✓ Branch 4 taken 2 times.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✓ Branch 7 taken 2 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 2 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 2 times.
✗ Branch 13 not taken.
✓ Branch 14 taken 2 times.
✗ Branch 16 not taken.
✓ Branch 17 taken 2 times.
|
2 | allocate(character(len=charlen) :: tlist(size(list))) |
77 |
7/14✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 2 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 2 times.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✗ Branch 7 not taken.
✓ Branch 8 taken 11 times.
✓ Branch 9 taken 2 times.
✓ Branch 10 taken 11 times.
✗ Branch 11 not taken.
✗ Branch 12 not taken.
✓ Branch 13 taken 11 times.
|
15 | tlist = list |
78 |
2/2✓ Branch 0 taken 11 times.
✓ Branch 1 taken 2 times.
|
13 | do i = 1, size(tlist) |
79 |
2/4✓ Branch 1 taken 11 times.
✗ Branch 2 not taken.
✗ Branch 3 not taken.
✓ Branch 4 taken 11 times.
|
13 | list(i) = to_upper(list(i)) |
80 | end do | ||
81 | end if | ||
82 |
2/2✓ Branch 0 taken 369 times.
✓ Branch 1 taken 156 times.
|
525 | do i = 1, size(list) |
83 | 369 | loc = minloc(list(i:),dim=1) | |
84 |
2/2✓ Branch 0 taken 352 times.
✓ Branch 1 taken 17 times.
|
369 | if(loc.eq.1) cycle |
85 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 16 times.
|
17 | if(lcase_) call cswap(tlist(i),tlist(loc+i-1)) |
86 | 173 | call cswap(list(i),list(loc+i-1)) | |
87 | end do | ||
88 |
6/8✓ Branch 0 taken 2 times.
✓ Branch 1 taken 154 times.
✓ Branch 2 taken 11 times.
✓ Branch 3 taken 2 times.
✓ Branch 4 taken 11 times.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✓ Branch 7 taken 11 times.
|
167 | if(lcase_) list=tlist |
89 | |||
90 |
2/2✓ Branch 0 taken 2 times.
✓ Branch 1 taken 154 times.
|
156 | end subroutine sort_str |
91 | !############################################################################### | ||
92 | |||
93 | |||
94 | !############################################################################### | ||
95 |
1/2✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
|
2 | function sort_str_order(list,lcase) result(order) |
96 | !! Sort a list of strings and return the order. | ||
97 | implicit none | ||
98 | |||
99 | ! Arguments | ||
100 | character(*), dimension(:), intent(inout) :: list | ||
101 | !! List of strings to be sorted. | ||
102 | logical, optional, intent(in) :: lcase | ||
103 | !! Optional. Boolean whether case insensitive sorting is required. | ||
104 | !! Default is .false. | ||
105 | |||
106 | ! Local variables | ||
107 | integer :: i,loc | ||
108 | !! Loop index. | ||
109 | integer :: charlen | ||
110 | !! Length of the strings. | ||
111 | logical :: lcase_ | ||
112 | !! Boolean whether case insensitive sorting is required. | ||
113 | 2 | character(:), allocatable, dimension(:) :: tlist | |
114 | !! Temporary list for case insensitive sorting. | ||
115 | |||
116 | 2 | integer, allocatable, dimension(:) :: torder,order | |
117 | !! Order of the sorted list. | ||
118 | |||
119 | 2 | charlen = len(list(1)) | |
120 | 2 | lcase_ = .false. | |
121 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
|
2 | if(present(lcase))then |
122 |
1/2✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
|
1 | if(lcase)then |
123 | 1 | lcase_ = lcase | |
124 |
8/16✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
✓ Branch 4 taken 1 times.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✓ Branch 7 taken 1 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 1 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 1 times.
✗ Branch 13 not taken.
✓ Branch 14 taken 1 times.
✗ Branch 16 not taken.
✓ Branch 17 taken 1 times.
|
1 | allocate(character(len=charlen) :: tlist(size(list))) |
125 |
7/14✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✗ Branch 7 not taken.
✓ Branch 8 taken 5 times.
✓ Branch 9 taken 1 times.
✓ Branch 10 taken 5 times.
✗ Branch 11 not taken.
✗ Branch 12 not taken.
✓ Branch 13 taken 5 times.
|
7 | tlist = list |
126 |
2/2✓ Branch 0 taken 5 times.
✓ Branch 1 taken 1 times.
|
6 | do i = 1, size(tlist) |
127 |
2/4✓ Branch 1 taken 5 times.
✗ Branch 2 not taken.
✗ Branch 3 not taken.
✓ Branch 4 taken 5 times.
|
6 | list(i) = to_upper(list(i)) |
128 | end do | ||
129 | end if | ||
130 | end if | ||
131 | |||
132 |
7/14✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 2 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 2 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 2 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 2 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 2 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 2 times.
|
2 | allocate(torder(size(list))) |
133 |
2/2✓ Branch 0 taken 10 times.
✓ Branch 1 taken 2 times.
|
12 | do i = 1, size(list) |
134 | 12 | torder(i) = i | |
135 | end do | ||
136 | |||
137 |
2/2✓ Branch 0 taken 10 times.
✓ Branch 1 taken 2 times.
|
12 | do i = 1, size(list) |
138 | 10 | loc = minloc(list(i:),dim=1) | |
139 |
2/2✓ Branch 0 taken 8 times.
✓ Branch 1 taken 2 times.
|
10 | if(loc.eq.1) cycle |
140 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
|
2 | if(lcase_) call cswap(tlist(i),tlist(loc+i-1)) |
141 | 2 | call cswap(list(i),list(loc+i-1)) | |
142 | 4 | call iswap(torder(i),torder(loc+i-1)) | |
143 | end do | ||
144 | |||
145 |
7/14✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 2 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 2 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 2 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 2 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 2 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 2 times.
|
2 | allocate(order(size(list))) |
146 |
2/2✓ Branch 0 taken 10 times.
✓ Branch 1 taken 2 times.
|
12 | do i = 1, size(list) |
147 |
3/4✓ Branch 0 taken 30 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 10 times.
✓ Branch 3 taken 20 times.
|
32 | order(i) = findloc(torder,i,dim=1) |
148 | end do | ||
149 | |||
150 |
6/8✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
✓ Branch 2 taken 5 times.
✓ Branch 3 taken 1 times.
✓ Branch 4 taken 5 times.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✓ Branch 7 taken 5 times.
|
7 | if(lcase_) list=tlist |
151 | |||
152 | 2 | return | |
153 |
3/4✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 1 times.
✓ Branch 3 taken 1 times.
|
2 | end function sort_str_order |
154 | !############################################################################### | ||
155 | |||
156 | |||
157 | !############################################################################### | ||
158 |
2/8✓ Branch 0 taken 7 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 7 times.
✗ Branch 4 not taken.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✗ Branch 7 not taken.
|
7 | subroutine isort1D(arr1,arr2,reverse) |
159 | !! Sort a 1D integer array from min to max. | ||
160 | implicit none | ||
161 | |||
162 | ! Arguments | ||
163 | integer, dimension(:), intent(inout) :: arr1 | ||
164 | !! Array to be sorted. | ||
165 | integer, dimension(:),intent(inout),optional :: arr2 | ||
166 | !! Optional. Second array to be sorted. | ||
167 | logical, optional, intent(in) :: reverse | ||
168 | !! Optional. Boolean whether to sort in reverse order. | ||
169 | |||
170 | ! Local variables | ||
171 | integer :: i,dim,loc | ||
172 | !! Loop index. | ||
173 | integer :: ibuff | ||
174 | !! Buffer for swapping elements. | ||
175 | logical :: reverse_ | ||
176 | !! Boolean whether to sort in reverse order. | ||
177 | |||
178 |
2/2✓ Branch 0 taken 2 times.
✓ Branch 1 taken 5 times.
|
7 | if(present(reverse))then |
179 | 2 | reverse_=reverse | |
180 | else | ||
181 | 5 | reverse_=.false. | |
182 | end if | ||
183 | |||
184 | 7 | dim=size(arr1,dim=1) | |
185 |
2/2✓ Branch 0 taken 49 times.
✓ Branch 1 taken 7 times.
|
56 | do i = 1, dim |
186 |
2/2✓ Branch 0 taken 6 times.
✓ Branch 1 taken 43 times.
|
49 | if(reverse_)then |
187 |
5/6✓ Branch 0 taken 6 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 16 times.
✓ Branch 3 taken 6 times.
✓ Branch 4 taken 12 times.
✓ Branch 5 taken 4 times.
|
22 | loc=maxloc(arr1(i:dim),dim=1)+i-1 |
188 | else | ||
189 |
5/6✓ Branch 0 taken 43 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 228 times.
✓ Branch 3 taken 43 times.
✓ Branch 4 taken 48 times.
✓ Branch 5 taken 180 times.
|
271 | loc=minloc(arr1(i:dim),dim=1)+i-1 |
190 | end if | ||
191 | 49 | ibuff=arr1(i) | |
192 | 49 | arr1(i)=arr1(loc) | |
193 | 49 | arr1(loc)=ibuff | |
194 | |||
195 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 49 times.
|
56 | if(present(arr2)) then |
196 | ✗ | ibuff=arr2(i) | |
197 | ✗ | arr2(i)=arr2(loc) | |
198 | ✗ | arr2(loc)=ibuff | |
199 | end if | ||
200 | end do | ||
201 | |||
202 | 7 | return | |
203 | end subroutine isort1D | ||
204 | !############################################################################### | ||
205 | |||
206 | |||
207 | !############################################################################### | ||
208 |
2/8✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 2 times.
✗ Branch 4 not taken.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✗ Branch 7 not taken.
|
2 | subroutine rsort1D(arr1,arr2,reverse) |
209 | !! Sort a 1D real array from min to max. | ||
210 | implicit none | ||
211 | |||
212 | ! Arguments | ||
213 | real(real32), dimension(:), intent(inout) :: arr1 | ||
214 | !! Array to be sorted. | ||
215 | integer, dimension(:),intent(inout),optional :: arr2 | ||
216 | !! Optional. Second array to be sorted. | ||
217 | logical, optional, intent(in) :: reverse | ||
218 | !! Optional. Boolean whether to sort in reverse order. | ||
219 | |||
220 | ! Local variables | ||
221 | integer :: i,dim,loc | ||
222 | !! Loop index. | ||
223 | integer :: ibuff | ||
224 | !! Buffer for swapping elements. | ||
225 | real(real32) :: rbuff | ||
226 | !! Buffer for swapping elements. | ||
227 | logical :: reverse_ | ||
228 | !! Boolean whether to sort in reverse order. | ||
229 | |||
230 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
|
2 | if(present(reverse))then |
231 | 1 | reverse_=reverse | |
232 | else | ||
233 | 1 | reverse_=.false. | |
234 | end if | ||
235 | |||
236 | 2 | dim=size(arr1,dim=1) | |
237 |
2/2✓ Branch 0 taken 10 times.
✓ Branch 1 taken 2 times.
|
12 | do i = 1, dim |
238 | select case(reverse_) | ||
239 | case(.true.) | ||
240 |
6/10✓ Branch 0 taken 5 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 5 times.
✗ Branch 3 not taken.
✗ Branch 4 not taken.
✗ Branch 5 not taken.
✓ Branch 6 taken 15 times.
✓ Branch 7 taken 5 times.
✓ Branch 8 taken 6 times.
✓ Branch 9 taken 9 times.
|
20 | loc=maxloc(arr1(i:dim),dim=1)+i-1 |
241 | case default | ||
242 |
8/12✓ Branch 0 taken 5 times.
✓ Branch 1 taken 5 times.
✓ Branch 2 taken 5 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 5 times.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✗ Branch 7 not taken.
✓ Branch 8 taken 15 times.
✓ Branch 9 taken 5 times.
✓ Branch 10 taken 5 times.
✓ Branch 11 taken 10 times.
|
25 | loc=minloc(arr1(i:dim),dim=1)+i-1 |
243 | end select | ||
244 | 10 | rbuff = arr1(i) | |
245 | 10 | arr1(i) = arr1(loc) | |
246 | 10 | arr1(loc) = rbuff | |
247 | |||
248 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 10 times.
|
12 | if(present(arr2)) then |
249 | ✗ | ibuff = arr2(i) | |
250 | ✗ | arr2(i) = arr2(loc) | |
251 | ✗ | arr2(loc) = ibuff | |
252 | end if | ||
253 | end do | ||
254 | |||
255 | 2 | return | |
256 | end subroutine rsort1D | ||
257 | !############################################################################### | ||
258 | |||
259 | |||
260 | !############################################################################### | ||
261 |
1/2✓ Branch 0 taken 7 times.
✗ Branch 1 not taken.
|
7 | pure recursive subroutine quicksort(arr, low, high) |
262 | !! Sort a 1D real array from min to max. | ||
263 | !! | ||
264 | !! This is a recursive implementation of the quicksort algorithm. | ||
265 | implicit none | ||
266 | |||
267 | ! Arguments | ||
268 | real(real32), dimension(:), intent(inout) :: arr | ||
269 | !! Array to be sorted. | ||
270 | integer, intent(in) :: low, high | ||
271 | !! Lower and upper bounds of the array to be sorted. | ||
272 | |||
273 | ! Local variables | ||
274 | integer :: i, j | ||
275 | !! Loop indices. | ||
276 | real(real32) :: pivot, temp | ||
277 | !! Pivot element and temporary buffer. | ||
278 | |||
279 |
1/2✓ Branch 0 taken 7 times.
✗ Branch 1 not taken.
|
7 | if (low .lt. high) then |
280 | 7 | pivot = arr((low + high) / 2) | |
281 | 7 | i = low | |
282 | 7 | j = high | |
283 | 1 | do | |
284 |
2/2✓ Branch 0 taken 8 times.
✓ Branch 1 taken 4 times.
|
12 | do while (arr(i) .lt. pivot .and. i .lt. high) |
285 | 4 | i = i + 1 | |
286 | end do | ||
287 |
2/2✓ Branch 0 taken 8 times.
✓ Branch 1 taken 8 times.
|
16 | do while (arr(j) .gt. pivot .and. j .gt. low) |
288 | 8 | j = j - 1 | |
289 | end do | ||
290 |
1/2✓ Branch 0 taken 8 times.
✗ Branch 1 not taken.
|
8 | if (i .le. j) then |
291 | 8 | temp = arr(i) | |
292 | 8 | arr(i) = arr(j) | |
293 | 8 | arr(j) = temp | |
294 | 8 | i = i + 1 | |
295 | 8 | j = j - 1 | |
296 | end if | ||
297 | ! Exit the loop when indices cross | ||
298 |
2/2✓ Branch 0 taken 7 times.
✓ Branch 1 taken 1 times.
|
8 | if (i .gt. j) exit |
299 | end do | ||
300 | ! Recursively apply quicksort to both partitions | ||
301 |
2/2✓ Branch 0 taken 3 times.
✓ Branch 1 taken 4 times.
|
7 | if (low .lt. j) call quicksort(arr, low, j) |
302 |
2/2✓ Branch 0 taken 2 times.
✓ Branch 1 taken 5 times.
|
7 | if (i .lt. high) call quicksort(arr, i, high) |
303 | end if | ||
304 | 7 | end subroutine quicksort | |
305 | !############################################################################### | ||
306 | |||
307 | |||
308 | !############################################################################### | ||
309 | ✗ | subroutine isort2D(arr, idx) | |
310 | !! Sort a 2D array along the first column. | ||
311 | implicit none | ||
312 | |||
313 | ! Arguments | ||
314 | integer, intent(in) :: idx | ||
315 | !! Index of 1st column to sort by. | ||
316 | integer, dimension(:,:), intent(inout) :: arr | ||
317 | !! Array to be sorted. | ||
318 | |||
319 | ! Local variables | ||
320 | integer :: i | ||
321 | !! Loop indices. | ||
322 | integer :: len, loc | ||
323 | !! Length of the array and location of the minimum element. | ||
324 | ✗ | integer, dimension(size(arr,dim=1)) :: buff | |
325 | !! Buffer for swapping elements. | ||
326 | |||
327 | ✗ | len = size(arr,dim=2) | |
328 | ✗ | do i = 1, len | |
329 | ✗ | loc = minloc(arr(idx,i:len),dim=1) | |
330 | ✗ | if(loc.eq.1) cycle | |
331 | ✗ | loc = loc + i - 1 | |
332 | ✗ | buff(:) = arr(:,i) | |
333 | ✗ | arr(:,i) = arr(:,loc) | |
334 | ✗ | arr(:,loc) = buff(:) | |
335 | end do | ||
336 | |||
337 | ✗ | end subroutine isort2D | |
338 | !############################################################################### | ||
339 | |||
340 | |||
341 | !############################################################################### | ||
342 | ✗ | subroutine rsort2D(arr, idx) | |
343 | !! Sort a 2D array along the first column. | ||
344 | implicit none | ||
345 | |||
346 | ! Arguments | ||
347 | integer, intent(in) :: idx | ||
348 | !! Index of 1st column to sort by. | ||
349 | real(real32), dimension(:,:), intent(inout) :: arr | ||
350 | !! Array to be sorted. | ||
351 | |||
352 | ! Local variables | ||
353 | integer :: i | ||
354 | !! Loop indices. | ||
355 | integer :: len, loc | ||
356 | !! Length of the array and location of the minimum element. | ||
357 | ✗ | real(real32), dimension(size(arr,dim=1)) :: buff | |
358 | !! Buffer for swapping elements. | ||
359 | |||
360 | ✗ | len = size(arr,dim=2) | |
361 | ✗ | do i = 1, len | |
362 | ✗ | loc = minloc(arr(idx,i:len),dim=1) | |
363 | ✗ | if(loc.eq.1) cycle | |
364 | ✗ | loc = loc + i - 1 | |
365 | ✗ | buff(:) = arr(:,i) | |
366 | ✗ | arr(:,i) = arr(:,loc) | |
367 | ✗ | arr(:,loc) = buff(:) | |
368 | end do | ||
369 | |||
370 | ✗ | end subroutine rsort2D | |
371 | !############################################################################### | ||
372 | |||
373 | |||
374 | !############################################################################### | ||
375 | 4 | subroutine iset(arr) | |
376 | !! Reduce an integer array to its unique elements. | ||
377 | implicit none | ||
378 | |||
379 | ! Arguments | ||
380 | integer, dimension(:), allocatable, intent(inout) :: arr | ||
381 | !! Array to be reduced. | ||
382 | |||
383 | ! Local variables | ||
384 | integer :: i,n | ||
385 | !! Loop index. | ||
386 | 4 | integer, dimension(:), allocatable :: tmp_arr | |
387 | !! Temporary array for storing unique elements. | ||
388 | |||
389 | |||
390 | 4 | call sort1D(arr) | |
391 |
7/14✓ Branch 0 taken 4 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 4 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 4 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 4 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 4 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 4 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 4 times.
|
4 | allocate(tmp_arr(size(arr))) |
392 | |||
393 | 4 | tmp_arr(1) = arr(1) | |
394 | 4 | n=1 | |
395 |
2/2✓ Branch 0 taken 34 times.
✓ Branch 1 taken 4 times.
|
38 | do i = 2, size(arr) |
396 |
2/2✓ Branch 0 taken 32 times.
✓ Branch 1 taken 2 times.
|
34 | if(arr(i)==tmp_arr(n)) cycle |
397 | 2 | n = n + 1 | |
398 | 6 | tmp_arr(n) = arr(i) | |
399 | end do | ||
400 |
8/16✗ Branch 0 not taken.
✓ Branch 1 taken 4 times.
✓ Branch 3 taken 4 times.
✗ Branch 4 not taken.
✗ Branch 5 not taken.
✓ Branch 6 taken 4 times.
✗ Branch 7 not taken.
✓ Branch 8 taken 4 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 4 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 4 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 4 times.
✗ Branch 17 not taken.
✓ Branch 18 taken 4 times.
|
4 | deallocate(arr); allocate(arr(n)) |
401 |
2/2✓ Branch 0 taken 6 times.
✓ Branch 1 taken 4 times.
|
10 | arr(:n) = tmp_arr(:n) |
402 | !call move_alloc(tmp_arr, arr) | ||
403 | |||
404 |
1/2✓ Branch 0 taken 4 times.
✗ Branch 1 not taken.
|
4 | end subroutine iset |
405 | !############################################################################### | ||
406 | |||
407 | |||
408 | !############################################################################### | ||
409 | 2 | subroutine rset(arr, tol, count_list) | |
410 | !! Reduce a real array to its unique elements. | ||
411 | implicit none | ||
412 | |||
413 | ! Arguments | ||
414 | real(real32), dimension(:), allocatable, intent(inout) :: arr | ||
415 | !! Array to be reduced. | ||
416 | real(real32), intent(in), optional :: tol | ||
417 | !! Tolerance for comparing real numbers. | ||
418 | integer, dimension(:), allocatable, intent(out), optional :: count_list | ||
419 | !! List of counts for each unique element. | ||
420 | |||
421 | ! Local variables | ||
422 | integer :: i,n | ||
423 | !! Loop index. | ||
424 | real(real32) :: tol_ | ||
425 | !! Tolerance for comparing real numbers. | ||
426 | 2 | real(real32), dimension(:), allocatable :: tmp_arr | |
427 | !! Temporary array for storing unique elements. | ||
428 | 2 | integer, dimension(:), allocatable :: count_list_ | |
429 | !! List of counts for each unique element. | ||
430 | |||
431 | |||
432 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
|
2 | if(present(tol))then |
433 | 1 | tol_ = tol | |
434 | else | ||
435 | 1 | tol_ = 1.E-4_real32 | |
436 | end if | ||
437 | |||
438 | 2 | call quicksort(arr, 1, size(arr)) | |
439 |
7/14✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 2 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 2 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 2 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 2 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 2 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 2 times.
|
2 | allocate(tmp_arr(size(arr))) |
440 |
9/16✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 2 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 2 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 2 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 2 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 2 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 2 times.
✓ Branch 17 taken 11 times.
✓ Branch 18 taken 2 times.
|
13 | allocate(count_list_(size(arr)), source = 1) |
441 | |||
442 | 2 | tmp_arr(1) = arr(1) | |
443 | 2 | n=1 | |
444 |
2/2✓ Branch 0 taken 9 times.
✓ Branch 1 taken 2 times.
|
11 | do i = 2, size(arr) |
445 |
2/2✓ Branch 0 taken 4 times.
✓ Branch 1 taken 5 times.
|
9 | if(abs(arr(i)-tmp_arr(n)).lt.tol_)then |
446 | 4 | count_list_(i) = count_list_(i) + 1 | |
447 | 4 | cycle | |
448 | end if | ||
449 | 5 | n = n + 1 | |
450 | 7 | tmp_arr(n) = arr(i) | |
451 | end do | ||
452 |
8/16✗ Branch 0 not taken.
✓ Branch 1 taken 2 times.
✓ Branch 3 taken 2 times.
✗ Branch 4 not taken.
✗ Branch 5 not taken.
✓ Branch 6 taken 2 times.
✗ Branch 7 not taken.
✓ Branch 8 taken 2 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 2 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 2 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 2 times.
✗ Branch 17 not taken.
✓ Branch 18 taken 2 times.
|
2 | deallocate(arr); allocate(arr(n)) |
453 |
2/2✓ Branch 0 taken 7 times.
✓ Branch 1 taken 2 times.
|
9 | arr(:n) = tmp_arr(:n) |
454 |
1/12✗ Branch 0 not taken.
✓ Branch 1 taken 2 times.
✗ Branch 2 not taken.
✗ Branch 3 not taken.
✗ Branch 4 not taken.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✗ Branch 7 not taken.
✗ Branch 8 not taken.
✗ Branch 9 not taken.
✗ Branch 10 not taken.
✗ Branch 11 not taken.
|
2 | if(present(count_list)) count_list = count_list_(:n) |
455 | |||
456 |
2/4✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 2 times.
✗ Branch 3 not taken.
|
2 | end subroutine rset |
457 | !############################################################################### | ||
458 | |||
459 | |||
460 | !############################################################################### | ||
461 | 59 | subroutine cset(arr,lcase,lkeep_size) | |
462 | !! Reduce a character array to its unique elements. | ||
463 | !! | ||
464 | !! This subroutine reduces a character array to its unique elements. | ||
465 | !! i.e. each string in the array is compared with the rest of the strings | ||
466 | !! in the array and if a match is found, the string is removed. | ||
467 | !! This results in only the unique strings being preserved. | ||
468 | implicit none | ||
469 | |||
470 | ! Arguments | ||
471 | character(*), allocatable, dimension(:), intent(inout) :: arr | ||
472 | !! Array to be reduced. | ||
473 | logical, intent(in), optional :: lcase | ||
474 | !! Optional. Boolean whether to perform case insensitive comparison. | ||
475 | logical, intent(in), optional :: lkeep_size | ||
476 | !! Optional. Boolean whether to keep the original size of the array. | ||
477 | |||
478 | ! Local variables | ||
479 | integer :: i, n | ||
480 | !! Loop index. | ||
481 | logical :: lkeep_size_ | ||
482 | !! Boolean whether to keep the original size of the array. | ||
483 | 59 | character(len=:), allocatable, dimension(:) :: tmp_arr | |
484 | !! Temporary array for storing unique elements. | ||
485 | logical :: lcase_ | ||
486 | !! Boolean whether to perform case insensitive comparison. | ||
487 | |||
488 | |||
489 | 59 | if(present(lcase))then | |
490 | 1 | lcase_ = lcase | |
491 | else | ||
492 | 58 | lcase_ = .false. | |
493 | end if | ||
494 | 59 | call sort_str(arr,lcase_) | |
495 | |||
496 |
8/16✓ Branch 0 taken 59 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 59 times.
✓ Branch 4 taken 59 times.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✓ Branch 7 taken 59 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 59 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 59 times.
✗ Branch 13 not taken.
✓ Branch 14 taken 59 times.
✗ Branch 16 not taken.
✓ Branch 17 taken 59 times.
|
59 | allocate(character(len=len(arr(1))) :: tmp_arr(size(arr))) |
497 |
2/4✓ Branch 0 taken 59 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 59 times.
|
59 | tmp_arr(1) = arr(1) |
498 | 59 | n=1 | |
499 | |||
500 |
2/2✓ Branch 0 taken 110 times.
✓ Branch 1 taken 59 times.
|
169 | do i = 2, size(arr) |
501 |
4/6✓ Branch 0 taken 5 times.
✓ Branch 1 taken 105 times.
✓ Branch 3 taken 5 times.
✗ Branch 4 not taken.
✗ Branch 5 not taken.
✓ Branch 6 taken 5 times.
|
110 | if(lcase_) arr(i) = to_lower(arr(i)) |
502 |
4/6✓ Branch 2 taken 110 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 110 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 61 times.
✓ Branch 7 taken 49 times.
|
110 | if(trim(arr(i)).eq.trim(tmp_arr(n))) cycle |
503 | 49 | n = n + 1 | |
504 |
2/4✓ Branch 0 taken 49 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 49 times.
|
108 | tmp_arr(n) = arr(i) |
505 | end do | ||
506 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 58 times.
|
59 | if(present(lkeep_size))then |
507 | 1 | lkeep_size_=lkeep_size | |
508 | else | ||
509 | 58 | lkeep_size_=.false. | |
510 | end if | ||
511 | |||
512 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 58 times.
|
59 | if(lkeep_size_)then |
513 |
1/2✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
|
1 | call move_alloc(tmp_arr,arr) |
514 | else | ||
515 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 58 times.
|
58 | deallocate(arr) |
516 |
8/16✓ Branch 0 taken 58 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 58 times.
✓ Branch 4 taken 58 times.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✓ Branch 7 taken 58 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 58 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 58 times.
✗ Branch 13 not taken.
✓ Branch 14 taken 58 times.
✗ Branch 16 not taken.
✓ Branch 17 taken 58 times.
|
58 | allocate(arr(n)) |
517 |
4/6✓ Branch 0 taken 104 times.
✓ Branch 1 taken 58 times.
✓ Branch 2 taken 104 times.
✗ Branch 3 not taken.
✗ Branch 4 not taken.
✓ Branch 5 taken 104 times.
|
162 | arr(:n) = tmp_arr(:n) |
518 | end if | ||
519 | |||
520 |
4/4✓ Branch 0 taken 1 times.
✓ Branch 1 taken 58 times.
✓ Branch 2 taken 58 times.
✓ Branch 3 taken 1 times.
|
118 | end subroutine cset |
521 | !############################################################################### | ||
522 | |||
523 | |||
524 | !############################################################################### | ||
525 | 2 | subroutine iswap(value1,value2) | |
526 | !! Swap two integers. | ||
527 | implicit none | ||
528 | |||
529 | ! Arguments | ||
530 | integer, intent(inout) :: value1, value2 | ||
531 | !! Integers to be swapped. | ||
532 | |||
533 | ! Local variables | ||
534 | integer :: itmp1 | ||
535 | !! Temporary buffer for swapping elements. | ||
536 | |||
537 | 2 | itmp1 = value1 | |
538 | 2 | value1 = value2 | |
539 | 2 | value2 = itmp1 | |
540 | 2 | end subroutine iswap | |
541 | !############################################################################### | ||
542 | |||
543 | |||
544 | !############################################################################### | ||
545 | 1 | subroutine rswap(value1,value2) | |
546 | !! Swap two reals. | ||
547 | implicit none | ||
548 | |||
549 | ! Arguments | ||
550 | real(real32), intent(inout) :: value1, value2 | ||
551 | !! Reals to be swapped. | ||
552 | |||
553 | ! Local variables | ||
554 | real(real32) :: rtmp1 | ||
555 | !! Temporary buffer for swapping elements. | ||
556 | |||
557 | 1 | rtmp1 = value1 | |
558 | 1 | value1 = value2 | |
559 | 1 | value2 = rtmp1 | |
560 | 1 | end subroutine rswap | |
561 | !############################################################################### | ||
562 | |||
563 | |||
564 | !############################################################################### | ||
565 | 21 | subroutine cswap(c1,c2) | |
566 | !! Swap two character strings. | ||
567 | implicit none | ||
568 | |||
569 | ! Arguments | ||
570 | character(*), intent(inout) :: c1, c2 | ||
571 | !! Strings to be swapped. | ||
572 | |||
573 | ! Local variables | ||
574 | 21 | character(len=:), allocatable :: ctmp | |
575 | !! Temporary buffer for swapping elements. | ||
576 | |||
577 |
2/6✗ Branch 0 not taken.
✗ Branch 1 not taken.
✓ Branch 2 taken 21 times.
✗ Branch 3 not taken.
✗ Branch 4 not taken.
✓ Branch 5 taken 21 times.
|
21 | ctmp=c1 |
578 |
2/4✓ Branch 0 taken 21 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 21 times.
|
21 | c1=c2 |
579 |
2/4✓ Branch 0 taken 21 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 21 times.
|
21 | c2=ctmp |
580 |
2/4✓ Branch 0 taken 21 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 21 times.
✗ Branch 3 not taken.
|
42 | end subroutine cswap |
581 | !############################################################################### | ||
582 | |||
583 | |||
584 | !############################################################################### | ||
585 |
2/4✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 1 times.
✗ Branch 3 not taken.
|
1 | subroutine rswap_vec(vec1,vec2) |
586 | !! Swap two real vectors. | ||
587 | implicit none | ||
588 | |||
589 | ! Arguments | ||
590 | real(real32),dimension(:), intent(inout) :: vec1, vec2 | ||
591 | !! Vectors to be swapped. | ||
592 | |||
593 | ! Local variables | ||
594 | 1 | real(real32),allocatable,dimension(:)::tvec | |
595 | !! Temporary buffer for swapping elements. | ||
596 | |||
597 |
7/14✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 1 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 1 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 1 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 1 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 1 times.
|
1 | allocate(tvec(size(vec1))) |
598 |
4/8✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 1 times.
✗ Branch 3 not taken.
✗ Branch 4 not taken.
✗ Branch 5 not taken.
✓ Branch 6 taken 2 times.
✓ Branch 7 taken 1 times.
|
4 | tvec=vec1(:) |
599 |
2/2✓ Branch 0 taken 2 times.
✓ Branch 1 taken 1 times.
|
3 | vec1(:)=vec2(:) |
600 |
2/2✓ Branch 0 taken 2 times.
✓ Branch 1 taken 1 times.
|
3 | vec2(:)=tvec |
601 |
1/2✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
|
1 | end subroutine rswap_vec |
602 | !############################################################################### | ||
603 | |||
604 | |||
605 | !############################################################################### | ||
606 |
1/2✓ Branch 0 taken 4 times.
✗ Branch 1 not taken.
|
4 | subroutine ishuffle(arr,dim,seed) |
607 | !! Shuffle a 2D integer array. | ||
608 | implicit none | ||
609 | |||
610 | ! Arguments | ||
611 | integer, dimension(:,:), intent(inout) :: arr | ||
612 | !! Array to be shuffled. | ||
613 | integer, intent(in) :: dim | ||
614 | !! Dimension to shuffle along. | ||
615 | integer, intent(in), optional :: seed | ||
616 | !! Seed for random number generator. | ||
617 | |||
618 | ! Local variables | ||
619 | integer :: iseed | ||
620 | !! Seed for random number generator. | ||
621 | integer :: i, j, k, n_data, iother, istart | ||
622 | !! Loop indices. | ||
623 | integer :: i1s,i2s,i1e,i2e,j1s,j2s,j1e,j2e | ||
624 | !! Indices for swapping elements. | ||
625 | real(real32) :: r | ||
626 | !! Random number for shuffling. | ||
627 | 4 | integer, allocatable, dimension(:,:) :: tlist | |
628 | !! Temporary list for swapping elements. | ||
629 | |||
630 | |||
631 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 3 times.
|
4 | if(present(seed)) iseed = seed |
632 | |||
633 | 4 | call random_seed(iseed) | |
634 | 4 | n_data = size(arr,dim=dim) | |
635 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 4 times.
|
4 | if(dim.eq.1)then |
636 | ✗ | iother = 2 | |
637 | ✗ | i2s=1;i2e=size(arr,dim=iother) | |
638 | ✗ | j2s=1;j2e=size(arr,dim=iother) | |
639 | ✗ | allocate(tlist(1,size(arr,dim=iother))) | |
640 | else | ||
641 | 4 | iother = 1 | |
642 | 4 | i1s=1;i1e=size(arr,dim=iother) | |
643 | 4 | j1s=1;j1e=size(arr,dim=iother) | |
644 |
7/14✓ Branch 0 taken 4 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 4 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 4 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 4 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 4 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 4 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 4 times.
|
4 | allocate(tlist(size(arr,dim=iother),1)) |
645 | end if | ||
646 | 4 | istart=1 | |
647 |
2/2✓ Branch 0 taken 8 times.
✓ Branch 1 taken 4 times.
|
12 | do k = 1, 2 |
648 |
2/2✓ Branch 0 taken 74 times.
✓ Branch 1 taken 8 times.
|
86 | do i = 1, n_data |
649 | 74 | call random_number(r) | |
650 |
1/2✓ Branch 0 taken 74 times.
✗ Branch 1 not taken.
|
74 | j = istart + floor((n_data+1-istart)*r) |
651 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 74 times.
|
74 | if(dim.eq.1)then |
652 | ✗ | i1s=i;i1e=i | |
653 | ✗ | j1s=j;j1e=j | |
654 | else | ||
655 | 74 | i2s=i;i2e=i | |
656 | 74 | j2s=j;j2e=j | |
657 | end if | ||
658 |
4/4✓ Branch 0 taken 74 times.
✓ Branch 1 taken 74 times.
✓ Branch 2 taken 138 times.
✓ Branch 3 taken 74 times.
|
286 | tlist(:,:) = arr(i1s:i1e,i2s:i2e) |
659 |
9/10✓ Branch 0 taken 74 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 74 times.
✓ Branch 3 taken 74 times.
✓ Branch 4 taken 138 times.
✓ Branch 5 taken 74 times.
✓ Branch 6 taken 74 times.
✓ Branch 7 taken 74 times.
✓ Branch 8 taken 138 times.
✓ Branch 9 taken 74 times.
|
498 | arr(i1s:i1e,i2s:i2e) = arr(j1s:j1e,j2s:j2e) |
660 |
4/4✓ Branch 0 taken 74 times.
✓ Branch 1 taken 74 times.
✓ Branch 2 taken 138 times.
✓ Branch 3 taken 74 times.
|
294 | arr(j1s:j1e,j2s:j2e) = tlist(:,:) |
661 | end do | ||
662 | end do | ||
663 | |||
664 |
1/2✓ Branch 0 taken 4 times.
✗ Branch 1 not taken.
|
4 | end subroutine ishuffle |
665 | !############################################################################### | ||
666 | |||
667 | |||
668 | !############################################################################### | ||
669 |
1/2✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
|
1 | subroutine rshuffle(arr,dim,seed) |
670 | !! Shuffle a 2D real array. | ||
671 | implicit none | ||
672 | |||
673 | ! Arguments | ||
674 | real(real32), dimension(:,:), intent(inout) :: arr | ||
675 | !! Array to be shuffled. | ||
676 | integer, intent(in) :: dim | ||
677 | !! Dimension to shuffle along. | ||
678 | integer, intent(in), optional :: seed | ||
679 | !! Seed for random number generator. | ||
680 | |||
681 | ! Local variables | ||
682 | integer :: iseed | ||
683 | !! Seed for random number generator. | ||
684 | integer :: i, j, k, n_data, iother, istart | ||
685 | !! Loop indices. | ||
686 | integer :: i1s,i2s,i1e,i2e,j1s,j2s,j1e,j2e | ||
687 | !! Indices for swapping elements. | ||
688 | real(real32) :: r | ||
689 | !! Random number for shuffling. | ||
690 | 1 | real(real32), allocatable, dimension(:,:) :: tlist | |
691 | !! Temporary list for swapping elements. | ||
692 | |||
693 | |||
694 |
1/2✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
|
1 | if(present(seed)) iseed = seed |
695 | |||
696 | 1 | call random_seed(iseed) | |
697 | 1 | n_data = size(arr,dim=dim) | |
698 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
|
1 | if(dim.eq.1)then |
699 | ✗ | iother = 2 | |
700 | ✗ | i2s=1;i2e=size(arr,dim=iother) | |
701 | ✗ | j2s=1;j2e=size(arr,dim=iother) | |
702 | else | ||
703 | 1 | iother = 1 | |
704 | 1 | i1s=1;i1e=size(arr,dim=iother) | |
705 | 1 | j1s=1;j1e=size(arr,dim=iother) | |
706 | end if | ||
707 | 1 | istart=1 | |
708 |
7/14✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 1 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 1 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 1 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 1 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 1 times.
|
1 | allocate(tlist(1,size(arr,dim=iother))) |
709 |
2/2✓ Branch 0 taken 2 times.
✓ Branch 1 taken 1 times.
|
3 | do k = 1, 2 |
710 |
2/2✓ Branch 0 taken 10 times.
✓ Branch 1 taken 2 times.
|
13 | do i = 1, n_data |
711 | 10 | call random_number(r) | |
712 |
1/2✓ Branch 0 taken 10 times.
✗ Branch 1 not taken.
|
10 | j = istart + floor((n_data+1-istart)*r) |
713 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 10 times.
|
10 | if(dim.eq.1)then |
714 | ✗ | i1s=i;i1e=i | |
715 | ✗ | j1s=j;j1e=j | |
716 | else | ||
717 | 10 | i2s=i;i2e=i | |
718 | 10 | j2s=j;j2e=j | |
719 | end if | ||
720 |
4/4✓ Branch 0 taken 10 times.
✓ Branch 1 taken 10 times.
✓ Branch 2 taken 10 times.
✓ Branch 3 taken 10 times.
|
30 | tlist(1:1,:) = arr(i1s:i1e,i2s:i2e) |
721 |
9/10✓ Branch 0 taken 10 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 10 times.
✓ Branch 3 taken 10 times.
✓ Branch 4 taken 10 times.
✓ Branch 5 taken 10 times.
✓ Branch 6 taken 10 times.
✓ Branch 7 taken 10 times.
✓ Branch 8 taken 10 times.
✓ Branch 9 taken 10 times.
|
50 | arr(i1s:i1e,i2s:i2e) = arr(j1s:j1e,j2s:j2e) |
722 |
4/4✓ Branch 0 taken 10 times.
✓ Branch 1 taken 10 times.
✓ Branch 2 taken 10 times.
✓ Branch 3 taken 10 times.
|
32 | arr(j1s:j1e,j2s:j2e) = tlist(1:1,:) |
723 | end do | ||
724 | end do | ||
725 | |||
726 |
1/2✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
|
1 | end subroutine rshuffle |
727 | !############################################################################### | ||
728 | |||
729 | |||
730 | !############################################################################### | ||
731 | 23 | integer function icount(line,fs) | |
732 | !! Count the number of fields separated by specified delimiter. | ||
733 | !! | ||
734 | !! This function counts the number of fields separated by a specified | ||
735 | !! delimiter in a string. The default delimiter is a space. | ||
736 | implicit none | ||
737 | |||
738 | ! Arguments | ||
739 | character(*) :: line | ||
740 | !! String to be counted. | ||
741 | character(*), intent(in), optional :: fs | ||
742 | !! Optional. Delimiter (aka field separator). | ||
743 | |||
744 | ! Local variables | ||
745 | integer :: k | ||
746 | !! Loop index. | ||
747 | integer :: items, pos, length | ||
748 | !! Number of fields and position in the string. | ||
749 | 23 | character(len=:), allocatable :: fs_ | |
750 | !! Delimiter (aka field separator). | ||
751 | |||
752 | |||
753 | 23 | items=0 | |
754 | 23 | pos=1 | |
755 | 23 | length=1 | |
756 |
1/2✓ Branch 1 taken 1 times.
✗ Branch 2 not taken.
|
1 | if(present(fs)) length=len(trim(fs)) |
757 |
2/4✗ Branch 0 not taken.
✓ Branch 1 taken 23 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 23 times.
|
23 | allocate(character(len=length) :: fs_) |
758 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 22 times.
|
23 | if(present(fs)) then |
759 |
5/10✗ Branch 1 not taken.
✓ Branch 2 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
✓ Branch 5 taken 1 times.
✗ Branch 6 not taken.
✗ Branch 7 not taken.
✓ Branch 8 taken 1 times.
✓ Branch 9 taken 1 times.
✗ Branch 10 not taken.
|
1 | fs_=trim(fs) |
760 | else | ||
761 |
4/8✗ Branch 0 not taken.
✓ Branch 1 taken 22 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 22 times.
✓ Branch 4 taken 22 times.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✓ Branch 7 taken 22 times.
|
22 | fs_=" " |
762 | end if | ||
763 | |||
764 | 64 | loop: do | |
765 | 87 | k=verify(line(pos:),fs_) | |
766 |
2/2✓ Branch 0 taken 22 times.
✓ Branch 1 taken 65 times.
|
87 | if (k.eq.0) exit loop |
767 | 65 | items=items+1 | |
768 | 65 | pos=k+pos-1 | |
769 | 65 | k=scan(line(pos:),fs_) | |
770 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 64 times.
|
65 | if (k.eq.0) exit loop |
771 | 64 | pos=k+pos-1 | |
772 | end do loop | ||
773 | 23 | icount=items | |
774 | |||
775 |
3/4✓ Branch 0 taken 1 times.
✓ Branch 1 taken 22 times.
✓ Branch 2 taken 23 times.
✗ Branch 3 not taken.
|
46 | end function icount |
776 | !############################################################################### | ||
777 | |||
778 | |||
779 | !############################################################################### | ||
780 | 3 | subroutine grep(unit,input,lstart,lline,success) | |
781 | !! Search a file for a pattern. | ||
782 | !! | ||
783 | !! This subroutine searches a file for a pattern. It can search for the | ||
784 | !! first line that contains the pattern or for the first line that starts | ||
785 | !! with the pattern. | ||
786 | implicit none | ||
787 | |||
788 | ! Arguments | ||
789 | integer :: unit | ||
790 | !! Unit number of the file. | ||
791 | character(*) :: input | ||
792 | !! Pattern to search for. | ||
793 | logical, intent(in), optional :: lstart | ||
794 | !! Optional. Boolean whether to rewind file. | ||
795 | logical, intent(in), optional :: lline | ||
796 | !! Optional. Boolean whether the pattern is at the start of the line. | ||
797 | logical, intent(out), optional :: success | ||
798 | !! Optional. Boolean whether the pattern is found. | ||
799 | |||
800 | ! Local variables | ||
801 | integer :: iostat | ||
802 | !! I/O status. | ||
803 | character(1024) :: buffer | ||
804 | !! Buffer for reading lines. | ||
805 | logical :: lline_ | ||
806 | !! Boolean whether the pattern is at the start of the line. | ||
807 | logical :: success_ | ||
808 | !! Boolean whether the pattern is found. | ||
809 | |||
810 | |||
811 | 3 | lline_ = .false. | |
812 | 3 | success_ = .false. | |
813 | 3 | if(present(lstart))then | |
814 |
1/2✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
|
1 | if(lstart) rewind(unit) |
815 | else | ||
816 | 2 | rewind(unit) | |
817 | end if | ||
818 | |||
819 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 2 times.
|
3 | if(present(lline)) lline_ = lline |
820 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 2 times.
|
3 | if(lline_)then |
821 | ✗ | wholeloop: do | |
822 | 1 | read(unit,'(A100)',iostat=iostat) buffer | |
823 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
|
1 | if(is_iostat_end(iostat))then |
824 | ✗ | exit wholeloop | |
825 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
|
1 | elseif(iostat.ne.0)then |
826 | ✗ | call stop_program('I/O stat error encounted when reading file') | |
827 | end if | ||
828 |
3/6✓ Branch 2 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
|
1 | if(index(trim(buffer),trim(input)).eq.1)then |
829 | 1 | success_ = .true. | |
830 | 1 | exit wholeloop | |
831 | end if | ||
832 | end do wholeloop | ||
833 | else | ||
834 | 4 | greploop: do | |
835 | 6 | read(unit,'(A100)',iostat=iostat) buffer | |
836 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 5 times.
|
6 | if(is_iostat_end(iostat))then |
837 | 1 | exit greploop | |
838 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 5 times.
|
5 | elseif(iostat.ne.0)then |
839 | ✗ | call stop_program('I/O stat error encounted when reading file') | |
840 | end if | ||
841 |
4/6✓ Branch 2 taken 5 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 5 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 1 times.
✓ Branch 7 taken 4 times.
|
5 | if(index(trim(buffer),trim(input)).ne.0)then |
842 | 1 | success_ = .true. | |
843 | 1 | exit greploop | |
844 | end if | ||
845 | end do greploop | ||
846 | end if | ||
847 | |||
848 |
1/2✓ Branch 0 taken 3 times.
✗ Branch 1 not taken.
|
3 | if(present(success)) success = success_ |
849 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 2 times.
|
3 | end subroutine grep |
850 | !############################################################################### | ||
851 | |||
852 | |||
853 | !############################################################################### | ||
854 | ✗ | subroutine flagmaker(buffer,flag,i,skip,empty) | |
855 | !! Assign variables of flags from get_command_argument. | ||
856 | implicit none | ||
857 | |||
858 | ! Arguments | ||
859 | character(*), intent(inout) :: buffer | ||
860 | !! Buffer to be assigned a flag. | ||
861 | character(*), intent(in) :: flag | ||
862 | !! Flag to look for. | ||
863 | integer :: i | ||
864 | !! Index of command argument. | ||
865 | logical :: skip | ||
866 | !! Boolean whether to skip the next argument. | ||
867 | logical, intent(out) :: empty | ||
868 | !! Boolean whether the buffer is empty. | ||
869 | |||
870 | |||
871 | ✗ | skip = .false. | |
872 | ✗ | empty = .false. | |
873 | ✗ | if(len(trim(buffer)).eq.len(trim(flag))) then | |
874 | ✗ | call get_command_argument(i+1,buffer) | |
875 | ✗ | if(scan(buffer,'-').eq.1.or.buffer.eq.'') then | |
876 | ✗ | buffer="" | |
877 | ✗ | empty=.true. | |
878 | else | ||
879 | ✗ | skip=.true. | |
880 | end if | ||
881 | else | ||
882 | ✗ | buffer=buffer(len(trim(flag))+1:) | |
883 | end if | ||
884 | |||
885 | ✗ | end subroutine flagmaker | |
886 | !############################################################################### | ||
887 | |||
888 | |||
889 | !############################################################################### | ||
890 | 10 | subroutine jump(unit,linenum) | |
891 | !! Go to a specific line in a file. | ||
892 | implicit none | ||
893 | |||
894 | ! Arguments | ||
895 | integer :: unit | ||
896 | !! Unit number of the file. | ||
897 | integer :: linenum | ||
898 | !! Line number to jump to. | ||
899 | |||
900 | ! Local variables | ||
901 | integer :: i | ||
902 | !! Loop index. | ||
903 | |||
904 | |||
905 | 10 | rewind(unit) | |
906 |
2/2✓ Branch 0 taken 55 times.
✓ Branch 1 taken 10 times.
|
65 | do i = 1, linenum, 1 |
907 | 65 | read(unit,*) | |
908 | end do | ||
909 | |||
910 | 10 | end subroutine jump | |
911 | !############################################################################### | ||
912 | |||
913 | |||
914 | !############################################################################### | ||
915 | ✗ | subroutine file_check(unit,filename,action) | |
916 | !! Check if a file exists and open it. | ||
917 | implicit none | ||
918 | |||
919 | ! Arguments | ||
920 | integer, intent(inout) :: unit | ||
921 | !! Unit number of the file. | ||
922 | character(*), intent(inout) :: filename | ||
923 | !! Name of the file. | ||
924 | character(len=20), optional, intent(in) :: action | ||
925 | !! Optional. Action to be taken on the file. | ||
926 | |||
927 | ! Local variables | ||
928 | integer :: i | ||
929 | !! Loop index. | ||
930 | integer :: iostat | ||
931 | !! I/O status. | ||
932 | character(20) :: action_ | ||
933 | !! Action to be taken on the file. | ||
934 | logical :: filefound | ||
935 | !! Boolean whether the file is found. | ||
936 | |||
937 | |||
938 | ✗ | action_="READWRITE" | |
939 | ✗ | if(present(action)) action_=action | |
940 | ✗ | action_=to_upper(action_) | |
941 | ✗ | do i = 1, 5 | |
942 | ✗ | inquire(file=trim(filename),exist=filefound) | |
943 | ✗ | if(.not.filefound) then | |
944 | write(6,'("File name ",A," not found.")')& | ||
945 | ✗ | "'"//trim(filename)//"'" | |
946 | ✗ | write(6,'("Supply another filename: ")') | |
947 | ✗ | read(*,*) filename | |
948 | else | ||
949 | write(6,'("Using file ",A)') & | ||
950 | ✗ | "'"//trim(filename)//"'" | |
951 | ✗ | exit | |
952 | end if | ||
953 | ✗ | if(i.ge.4) then | |
954 | ✗ | stop "Nope" | |
955 | end if | ||
956 | end do | ||
957 | ✗ | if(trim(adjustl(action_)).eq.'NONE')then | |
958 | ✗ | write(6,*) "File found, but not opened." | |
959 | else | ||
960 | open(newunit=unit,file=trim(filename),& | ||
961 | ✗ | action=trim(action_),iostat=iostat) | |
962 | end if | ||
963 | |||
964 | ✗ | end subroutine file_check | |
965 | !############################################################################### | ||
966 | |||
967 | |||
968 | !############################################################################### | ||
969 | ✗ | subroutine touch(file) | |
970 | !! Create a directory if it does not exist. | ||
971 | implicit none | ||
972 | |||
973 | ! Arguments | ||
974 | character(*), intent(in) :: file | ||
975 | !! Directory to be created. | ||
976 | |||
977 | ! Local variables | ||
978 | logical :: exists | ||
979 | !! Boolean whether the directory exists. | ||
980 | |||
981 | ✗ | inquire(file=file, exist=exists) | |
982 | ✗ | if(.not.exists) call execute_command_line("mkdir -p "//file) | |
983 | ✗ | end subroutine touch | |
984 | !############################################################################### | ||
985 | |||
986 | |||
987 | !############################################################################### | ||
988 | 46 | function to_upper(buffer) result(upper) | |
989 | !! Convert a string to upper case. | ||
990 | implicit none | ||
991 | |||
992 | ! Arguments | ||
993 | character(*), intent(in) :: buffer | ||
994 | !! String to be converted to upper case. | ||
995 | character(len=:),allocatable :: upper | ||
996 | !! Upper case string. | ||
997 | |||
998 | ! Local variables | ||
999 | integer :: i,j | ||
1000 | !! Loop index. | ||
1001 | |||
1002 | |||
1003 |
1/2✗ Branch 1 not taken.
✓ Branch 2 taken 46 times.
|
46 | allocate(character(len=len(buffer)) :: upper) |
1004 |
2/2✓ Branch 0 taken 1235 times.
✓ Branch 1 taken 46 times.
|
1281 | do i = 1, len(buffer) |
1005 | 1235 | j=iachar(buffer(i:i)) | |
1006 |
2/2✓ Branch 0 taken 101 times.
✓ Branch 1 taken 1134 times.
|
1281 | if(j.ge.iachar("a").and.j.le.iachar("z"))then |
1007 | 101 | upper(i:i)=achar(j-32) | |
1008 | else | ||
1009 | 1134 | upper(i:i)=buffer(i:i) | |
1010 | end if | ||
1011 | end do | ||
1012 | |||
1013 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 46 times.
|
46 | end function to_upper |
1014 | !############################################################################### | ||
1015 | |||
1016 | |||
1017 | !############################################################################### | ||
1018 | 8 | function to_lower(buffer) result(lower) | |
1019 | !! Convert a string to lower case. | ||
1020 | implicit none | ||
1021 | |||
1022 | ! Arguments | ||
1023 | character(*), intent(in) :: buffer | ||
1024 | !! String to be converted to lower case. | ||
1025 | character(len=:), allocatable :: lower | ||
1026 | !! Lower case string. | ||
1027 | |||
1028 | ! Local variables | ||
1029 | integer :: i,j | ||
1030 | !! Loop index. | ||
1031 | |||
1032 | |||
1033 |
1/2✗ Branch 1 not taken.
✓ Branch 2 taken 8 times.
|
8 | allocate(character(len=len(buffer)) :: lower) |
1034 |
2/2✓ Branch 0 taken 2158 times.
✓ Branch 1 taken 8 times.
|
2166 | do i = 1, len(buffer) |
1035 | 2158 | j=iachar(buffer(i:i)) | |
1036 |
2/2✓ Branch 0 taken 7 times.
✓ Branch 1 taken 2151 times.
|
2166 | if(j.ge.iachar("A").and.j.le.iachar("Z"))then |
1037 | 7 | lower(i:i)=achar(j+32) | |
1038 | else | ||
1039 | 2151 | lower(i:i)=buffer(i:i) | |
1040 | end if | ||
1041 | end do | ||
1042 | |||
1043 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 8 times.
|
8 | end function to_lower |
1044 | !############################################################################### | ||
1045 | |||
1046 | |||
1047 | !############################################################################### | ||
1048 | 186 | function strip_null(buffer) result(stripped) | |
1049 | !! Strip null characters from a string. | ||
1050 | !! | ||
1051 | !! This is meant for handling strings passed from Python, which gain | ||
1052 | !! null characters at the end. The procedure finds the first null | ||
1053 | !! character and truncates the string at that point. | ||
1054 | !! Null characters are represented by ASCII code 0. | ||
1055 | implicit none | ||
1056 | |||
1057 | ! Arguments | ||
1058 | character(*), intent(in) :: buffer | ||
1059 | !! String to be stripped. | ||
1060 | character(len=len(buffer)) :: stripped | ||
1061 | !! Stripped string. | ||
1062 | |||
1063 | ! Local variables | ||
1064 | integer :: i | ||
1065 | !! Loop index. | ||
1066 | |||
1067 |
1/2✓ Branch 0 taken 186 times.
✗ Branch 1 not taken.
|
186 | stripped = "" |
1068 |
2/2✓ Branch 0 taken 561 times.
✓ Branch 1 taken 185 times.
|
746 | do i = 1, len(buffer) |
1069 |
2/2✓ Branch 0 taken 560 times.
✓ Branch 1 taken 1 times.
|
746 | if(iachar(buffer(i:i)).ne.0)then |
1070 | 560 | stripped(i:i)=buffer(i:i) | |
1071 | else | ||
1072 | 1 | exit | |
1073 | end if | ||
1074 | end do | ||
1075 | |||
1076 |
1/2✓ Branch 0 taken 186 times.
✗ Branch 1 not taken.
|
186 | end function strip_null |
1077 | !############################################################################### | ||
1078 | |||
1079 | end module raffle__misc | ||
1080 |