GCC Code Coverage Report


Directory: src/fortran/lib/
File: mod_misc.f90
Date: 2025-04-05 12:17:58
Exec Total Coverage
Lines: 288 359 80.2%
Functions: 0 0 -%
Branches: 407 758 53.7%

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