GCC Code Coverage Report


Directory: src/lib/
File: src/lib/mod_tools_infile.f90
Date: 2024-06-28 12:51:18
Exec Total Coverage
Lines: 96 128 75.0%
Functions: 0 0 -%
Branches: 140 309 45.3%

Line Branch Exec Source
1 !!!#############################################################################
2 !!! Code written by Ned Thaddeus Taylor and Francis Huw Davies
3 !!! Code part of the ARTEMIS group (Hepplestone research group).
4 !!! Think Hepplestone, think HRG.
5 !!!#############################################################################
6 !!! module contains customn input file reading functions and subroutines.
7 !!! module includes the following functionsand subroutines:
8 !!! - assign_val - assign a value to a variable
9 !!! - assign_vec - assign a vector to a variable
10 !!! - getline - return line using grep and goes back to start of line
11 !!! - rm_comments - remove comments from a string (anything after ! or #)
12 !!! - cat - cat lines until user-defined end string is encountered
13 !!! - stop_check - check for <STOP> file and LSTOP or LABORT tags inside
14 !!!#############################################################################
15 module infile_tools
16 use misc, only: grep,icount
17 implicit none
18
19 private
20
21 !!!-----------------------------------------------------
22 !!! assign a value to variable
23 !!!-----------------------------------------------------
24 !!! buffer = (S, io) sacrifical input character string
25 !!! variable = (*, in) variable to assign data to
26 !!! found = (I, io) count for finding variable
27 !!! keyword = (S, in, opt) keyword to start from
28 !!! num = (I, in, opt) number of tags in tag_list
29 !!! tag_list = (S, in, opt) list of tags to search for
30 !!!-----------------------------------------------------
31 interface assign_val
32 procedure assignI,assignR,assignD,assignS,assignL
33 end interface assign_val
34 interface assign_vec
35 procedure assignIvec,assignRvec,assignDvec
36 end interface assign_vec
37
38
39 public :: getline, rm_comments
40 public :: assign_val, assign_vec
41 public :: stop_check
42
43
44 !!!updated 2024/03/04
45
46
47 contains
48 !!!#############################################################################
49 !!! val outputs the section of buffer that occurs after an "="
50 !!!#############################################################################
51 11 function val(buffer)
52 character(*), intent(in) :: buffer
53 character(100) :: val
54
55
2/4
✓ Branch 1 taken 11 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 11 times.
✗ Branch 4 not taken.
11 val=trim(adjustl(buffer((scan(buffer,"=",back=.false.)+1):)))
56 11 return
57 11 end function val
58 !!!#############################################################################
59
60
61 !!!#############################################################################
62 !!! gets the line from a grep and assigns it to buffer
63 !!!#############################################################################
64 !!! unit = (I, in) unit to read from
65 !!! pattern = (S, in) pattern to grep for
66 !!! buffer = (S, io) buffer to assign line to
67 subroutine getline(unit,pattern,buffer)
68 integer, intent(in) :: unit
69 character(*), intent(in) :: pattern
70 character(*), intent(out) :: buffer
71
72 integer :: Reason
73
74 call grep(unit,pattern)
75 backspace(unit);read(unit,'(A)',iostat=Reason) buffer
76
77 end subroutine getline
78 !!!#############################################################################
79
80
81 !!!#############################################################################
82 !!! assign an integer to variable
83 !!!#############################################################################
84 1 subroutine assignI(buffer,variable,found,keyword)
85 integer, intent(inout) :: found
86 character(*), intent(inout) :: buffer
87 integer, intent(out) :: variable
88 character(*), optional, intent(in) :: keyword
89
90 character(1024) :: buffer2
91
92 1 if(present(keyword))then
93
4/8
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
✓ Branch 5 taken 1 times.
✗ Branch 6 not taken.
✗ Branch 7 not taken.
✓ Branch 8 taken 1 times.
1 buffer=buffer(index(buffer,keyword):)
94 end if
95
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 if(scan("=",buffer).ne.0) buffer2=val(buffer)
96
2/4
✓ Branch 2 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
✗ Branch 5 not taken.
1 if(trim(adjustl(buffer2)).ne.'') then
97 1 found=found+1
98 1 read(buffer2,*) variable
99 end if
100
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 end subroutine assignI
101 !!!#############################################################################
102
103
104 !!!#############################################################################
105 !!! assign an arbitrary length vector of integers to variable
106 !!!#############################################################################
107 2 subroutine assignIvec(buffer,variable,found,keyword)
108 integer, intent(inout) :: found
109 character(*), intent(inout) :: buffer
110 integer, dimension(:) :: variable
111 character(*), optional, intent(in) :: keyword
112
113 integer :: i
114 character(1024) :: buffer2
115
116
1/2
✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
2 if(present(keyword))then
117
4/8
✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 2 times.
✓ Branch 5 taken 2 times.
✗ Branch 6 not taken.
✗ Branch 7 not taken.
✓ Branch 8 taken 2 times.
2 buffer=buffer(index(buffer,keyword):)
118 end if
119
1/2
✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
2 if(scan("=",buffer).ne.0) buffer2=val(buffer)
120
2/4
✓ Branch 2 taken 2 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 2 times.
✗ Branch 5 not taken.
2 if(trim(adjustl(buffer2)).ne.'') then
121 2 found=found+1
122
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
2 if(icount(buffer2).eq.1.and.&
123
3/6
✗ Branch 0 not taken.
✓ Branch 1 taken 2 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 2 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 2 times.
2 icount(buffer2).ne.size(variable))then
124
1/2
✗ Branch 1 not taken.
✓ Branch 2 taken 1 times.
1 read(buffer2,*) variable(1)
125
6/10
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 1 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 1 times.
✓ Branch 12 taken 3 times.
✓ Branch 13 taken 1 times.
4 variable = variable(1)
126 else
127
8/14
✗ Branch 1 not taken.
✓ Branch 2 taken 1 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 1 times.
✗ Branch 7 not taken.
✓ Branch 8 taken 1 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 4 times.
✓ Branch 12 taken 3 times.
✓ Branch 13 taken 1 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 3 times.
✗ Branch 17 not taken.
✓ Branch 18 taken 3 times.
4 read(buffer2,*) (variable(i),i=1,size(variable))
128 end if
129 end if
130
1/2
✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
2 end subroutine assignIvec
131 !!!#############################################################################
132
133
134 !!!#############################################################################
135 !!! assign a real to variable
136 !!!#############################################################################
137 1 subroutine assignR(buffer,variable,found,keyword)
138 integer, intent(inout) :: found
139 character(*), intent(inout) :: buffer
140 real, intent(out) :: variable
141 character(*), optional, intent(in) :: keyword
142
143 character(1024) :: buffer2
144
145 1 if(present(keyword))then
146
4/8
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
✓ Branch 5 taken 1 times.
✗ Branch 6 not taken.
✗ Branch 7 not taken.
✓ Branch 8 taken 1 times.
1 buffer=buffer(index(buffer,keyword):)
147 end if
148
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 if(scan("=",buffer).ne.0) buffer2=val(buffer)
149
2/4
✓ Branch 2 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
✗ Branch 5 not taken.
1 if(trim(adjustl(buffer2)).ne.'') then
150 1 found=found+1
151 1 read(buffer2,*) variable
152 end if
153
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 end subroutine assignR
154 !!!#############################################################################
155
156
157 !!!#############################################################################
158 !!! assign a DP value to variable
159 !!!#############################################################################
160 2 subroutine assignRvec(buffer,variable,found,keyword)
161 integer, intent(inout) :: found
162 character(*), intent(inout) :: buffer
163 real, dimension(:), intent(out) :: variable
164 character(*), optional, intent(in) :: keyword
165
166 integer :: i
167 character(1024) :: buffer2
168
169
1/2
✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
2 if(present(keyword))then
170
4/8
✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 2 times.
✓ Branch 5 taken 2 times.
✗ Branch 6 not taken.
✗ Branch 7 not taken.
✓ Branch 8 taken 2 times.
2 buffer=buffer(index(buffer,keyword):)
171 end if
172
1/2
✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
2 if(scan("=",buffer).ne.0) buffer2=val(buffer)
173
2/4
✓ Branch 2 taken 2 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 2 times.
✗ Branch 5 not taken.
2 if(trim(adjustl(buffer2)).ne.'') then
174 2 found=found+1
175
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
2 if(icount(buffer2).eq.1.and.&
176
3/6
✗ Branch 0 not taken.
✓ Branch 1 taken 2 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 2 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 2 times.
2 icount(buffer2).ne.size(variable))then
177
1/2
✗ Branch 1 not taken.
✓ Branch 2 taken 1 times.
1 read(buffer2,*) variable(1)
178
6/10
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 1 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 1 times.
✓ Branch 12 taken 3 times.
✓ Branch 13 taken 1 times.
4 variable = variable(1)
179 else
180
8/14
✗ Branch 1 not taken.
✓ Branch 2 taken 1 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 1 times.
✗ Branch 7 not taken.
✓ Branch 8 taken 1 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 4 times.
✓ Branch 12 taken 3 times.
✓ Branch 13 taken 1 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 3 times.
✗ Branch 17 not taken.
✓ Branch 18 taken 3 times.
4 read(buffer2,*) (variable(i),i=1,size(variable))
181 end if
182 end if
183
1/2
✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
2 end subroutine assignRvec
184 !!!#############################################################################
185
186
187 !!!#############################################################################
188 !!! assign a double precision to variable
189 !!!#############################################################################
190 1 subroutine assignD(buffer,variable,found,keyword)
191 integer, intent(inout) :: found
192 character(*), intent(inout) :: buffer
193 double precision, intent(out) :: variable
194 character(*), optional, intent(in) :: keyword
195
196 character(1024) :: buffer2
197
198 1 if(present(keyword))then
199
4/8
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
✓ Branch 5 taken 1 times.
✗ Branch 6 not taken.
✗ Branch 7 not taken.
✓ Branch 8 taken 1 times.
1 buffer=buffer(index(buffer,keyword):)
200 end if
201
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 if(scan("=",buffer).ne.0) buffer2=val(buffer)
202
2/4
✓ Branch 2 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
✗ Branch 5 not taken.
1 if(trim(adjustl(buffer2)).ne.'') then
203 1 found=found+1
204 1 read(buffer2,*) variable
205 end if
206
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 end subroutine assignD
207 !!!#############################################################################
208
209
210 !!!#############################################################################
211 !!! assign an arbitrary length vector of DP to variable
212 !!!#############################################################################
213 2 subroutine assignDvec(buffer,variable,found,keyword)
214 integer, intent(inout) :: found
215 character(*), intent(inout) :: buffer
216 double precision, dimension(:), intent(out) :: variable
217 character(*), optional, intent(in) :: keyword
218
219 integer :: i
220 character(1024) :: buffer2
221
222
1/2
✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
2 if(present(keyword))then
223
4/8
✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 2 times.
✓ Branch 5 taken 2 times.
✗ Branch 6 not taken.
✗ Branch 7 not taken.
✓ Branch 8 taken 2 times.
2 buffer=buffer(index(buffer,keyword):)
224 end if
225
1/2
✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
2 if(scan("=",buffer).ne.0) buffer2=val(buffer)
226
2/4
✓ Branch 2 taken 2 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 2 times.
✗ Branch 5 not taken.
2 if(trim(adjustl(buffer2)).ne.'') then
227 2 found=found+1
228
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
2 if(icount(buffer2).eq.1.and.&
229
3/6
✗ Branch 0 not taken.
✓ Branch 1 taken 2 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 2 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 2 times.
2 icount(buffer2).ne.size(variable))then
230
1/2
✗ Branch 1 not taken.
✓ Branch 2 taken 1 times.
1 read(buffer2,*) variable(1)
231
6/10
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 1 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 1 times.
✓ Branch 12 taken 3 times.
✓ Branch 13 taken 1 times.
4 variable = variable(1)
232 else
233
8/14
✗ Branch 1 not taken.
✓ Branch 2 taken 1 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 1 times.
✗ Branch 7 not taken.
✓ Branch 8 taken 1 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 4 times.
✓ Branch 12 taken 3 times.
✓ Branch 13 taken 1 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 3 times.
✗ Branch 17 not taken.
✓ Branch 18 taken 3 times.
4 read(buffer2,*) (variable(i),i=1,size(variable))
234 end if
235 end if
236
1/2
✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
2 end subroutine assignDvec
237 !!!#############################################################################
238
239
240 !!!#############################################################################
241 !!! assign a string to variable
242 !!!#############################################################################
243 1 subroutine assignS(buffer,variable,found,keyword)
244 integer, intent(inout) :: found
245 character(*), intent(inout) :: buffer
246 character(*), intent(out) :: variable
247 character(*), optional, intent(in) :: keyword
248
249 character(1024)::buffer2
250
251 1 if(present(keyword))then
252
4/8
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
✓ Branch 5 taken 1 times.
✗ Branch 6 not taken.
✗ Branch 7 not taken.
✓ Branch 8 taken 1 times.
1 buffer=buffer(index(buffer,keyword):)
253 end if
254
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 if(scan("=",buffer).ne.0) buffer2=val(buffer)
255
2/4
✓ Branch 2 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
✗ Branch 5 not taken.
1 if(trim(adjustl(buffer2)).ne.'') then
256 1 found=found+1
257 1 read(buffer2,'(A)') variable
258 end if
259
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 end subroutine assignS
260 !!!#############################################################################
261
262
263 !!!#############################################################################
264 !!! assign a logical to variable (T/t/1 and F/f/0 accepted
265 !!!#############################################################################
266 1 subroutine assignL(buffer,variable,found,keyword)
267 integer, intent(inout) :: found
268 character(*), intent(inout) :: buffer
269 logical, intent(out) :: variable
270 character(*), optional, intent(in) :: keyword
271
272 character(1024)::buffer2
273
274 1 if(present(keyword))then
275
4/8
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
✓ Branch 5 taken 1 times.
✗ Branch 6 not taken.
✗ Branch 7 not taken.
✓ Branch 8 taken 1 times.
1 buffer=buffer(index(buffer,keyword):)
276 end if
277
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 if(scan("=",buffer).ne.0) buffer2=val(buffer)
278
2/4
✓ Branch 2 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
✗ Branch 5 not taken.
1 if(trim(adjustl(buffer2)).ne.'') then
279 1 found=found+1
280 if(index(buffer2,"T").ne.0.or.&
281
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 index(buffer2,"t").ne.0.or.&
282 index(buffer2,"1").ne.0) then
283 1 variable=.TRUE.
284 end if
285 if(index(buffer2,"F").ne.0.or.&
286
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 index(buffer2,"f").ne.0.or.&
287 index(buffer2,"0").ne.0) then
288 variable=.FALSE.
289 end if
290 end if
291
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 end subroutine assignL
292 !!!#############################################################################
293
294
295 !!!#############################################################################
296 !!! remove comment from a string (anything after ! or #)
297 !!!#############################################################################
298 !!! buffer = (S, io) sacrifical input character string
299 !!! iline = (I, in, opt) line number
300 1 subroutine rm_comments(buffer,iline)
301 implicit none
302 character(*), intent(inout) :: buffer
303 integer, optional, intent(in) :: iline
304
305 integer :: lbracket,rbracket,iline_
306
307 1 iline_=0
308 if(present(iline)) iline_=iline
309
310
3/6
✓ 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.
1 if(scan(buffer,'!').ne.0) buffer=buffer(:(scan(buffer,'!')-1))
311
1/6
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 2 not taken.
✗ Branch 3 not taken.
✗ Branch 4 not taken.
✗ Branch 5 not taken.
1 if(scan(buffer,'#').ne.0) buffer=buffer(:(scan(buffer,'#')-1))
312
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 do while(scan(buffer,'(').ne.0.or.scan(buffer,')').ne.0)
313 lbracket=scan(buffer,'(',back=.true.)
314 rbracket=scan(buffer(lbracket:),')')
315 if(lbracket.eq.0.or.rbracket.eq.0)then
316 write(6,'(A,I0)') &
317 ' NOTE: a bracketing error was encountered on line ',iline_
318 buffer=""
319 return
320 end if
321 rbracket=rbracket+lbracket-1
322 buffer=buffer(:(lbracket-1))//buffer((rbracket+1):)
323 end do
324
325 1 return
326
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 end subroutine rm_comments
327 !!!#############################################################################
328
329
330 !!!#############################################################################
331 !!! logical check for stop file
332 !!!#############################################################################
333 !!! file = (S, in, opt) file to check for
334 499 function stop_check(file) result(output)
335 implicit none
336 integer :: Reason,itmp1
337 integer :: unit
338 logical :: lfound
339 logical :: output
340 character(*), optional, intent(in) :: file
341 character(248) :: file_
342 character(128) :: buffer, tagname
343
344 499 unit = 999
345 499 file_ = "STOPCAR"
346 if(present(file)) file_ = file
347
348 499 output = .false.
349 !! check if file exists
350
1/2
✓ Branch 2 taken 499 times.
✗ Branch 3 not taken.
499 inquire(file=trim(file_),exist=lfound)
351
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 499 times.
499 file_if: if(lfound)then
352 itmp1 = 0
353 open(unit=unit, file=trim(file_))
354 !! read line-by-line
355 file_loop: do
356 read(unit,'(A)',iostat=Reason) buffer
357 if(Reason.ne.0) exit file_loop
358 call rm_comments(buffer)
359 if(trim(buffer).eq.'') cycle file_loop
360 tagname=trim(adjustl(buffer))
361 if(scan(buffer,"=").ne.0) tagname=trim(tagname(:scan(tagname,"=")-1))
362 select case(trim(tagname))
363 case("LSTOP")
364 call assignL(buffer,output,itmp1)
365 exit file_loop
366 case("LABORT")
367 call assignL(buffer,output,itmp1)
368 if(output)then
369 close(unit,status='delete')
370 stop "LABORT ENCOUNTERED IN STOP FILE ("//trim(file_)//")"
371 end if
372 end select
373 end do file_loop
374 close(unit,status='delete')
375 end if file_if
376
377
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 499 times.
998 end function stop_check
378 !!!#############################################################################
379
380 end module infile_tools
381