GCC Code Coverage Report


Directory: src/fortran/lib/
File: mod_tools_infile.f90
Date: 2025-06-15 07:27:34
Exec Total Coverage
Lines: 59 80 73.8%
Functions: 0 0 -%
Branches: 50 126 39.7%

Line Branch Exec Source
1 module raffle__tools_infile
2 !! This module contains a collection of tools for reading input files.
3 !!
4 !! Code written by Ned Thaddeus Taylor and Francis Huw Davies
5 !! Code part of the ARTEMIS group (Hepplestone research group).
6 !! Think Hepplestone, think HRG.
7 !! Original distribution: https://github.com/ExeQuantCode/ARTEMIS
8 !! This module is distributed under the CC-BY-3.0 license.
9 !! License: http://creativecommons.org/licenses/by/3.0/
10 !! This module has been copied and modified with permission from the
11 !! original authors.
12 use raffle__constants, only: real32
13 use raffle__misc, only: grep,icount
14
15 implicit none
16
17
18 private
19 public :: getline, rm_comments
20 public :: assign_val, assign_vec
21
22
23 interface assign_val
24 procedure assignI, assignR, assignS, assignL
25 end interface assign_val
26
27 interface assign_vec
28 procedure assignIvec, assignRvec
29 end interface assign_vec
30
31
32
33 contains
34
35 !###############################################################################
36 26 function val(buffer)
37 !! Return the section of buffer that occurs after an "=".
38 implicit none
39
40 ! Arguments
41 character(*), intent(in) :: buffer
42 !! The input buffer.
43
44 ! Local variables
45 character(100) :: val
46 !! The output value.
47
48
2/4
✓ Branch 1 taken 26 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 26 times.
✗ Branch 4 not taken.
26 val = trim( adjustl( buffer((scan(buffer,"=",back=.false.)+1):) ) )
49
50 26 end function val
51 !###############################################################################
52
53
54 !###############################################################################
55 subroutine getline(unit, pattern, buffer)
56 !! Get the line from a grep and assign it to buffer.
57 implicit none
58
59 ! Arguments
60 integer, intent(in) :: unit
61 !! The unit to read from.
62 character(*), intent(in) :: pattern
63 !! The pattern to grep for.
64 character(*), intent(out) :: buffer
65 !! The buffer to assign the line to.
66
67 ! Local variables
68 integer :: iostat
69 !! input output status
70
71 call grep(unit,pattern)
72 backspace(unit)
73 read(unit,'(A)',iostat=iostat) buffer
74
75 end subroutine getline
76 !###############################################################################
77
78
79 !###############################################################################
80 1 subroutine assignI(buffer, variable, found, keyword)
81 !! Assign an integer to a variable.
82 implicit none
83
84 ! Arguments
85 integer, intent(inout) :: found
86 !! The number of variables found. External counter
87 character(*), intent(inout) :: buffer
88 !! The buffer to read from.
89 integer, intent(out) :: variable
90 !! The variable to assign to.
91 character(*), optional, intent(in) :: keyword
92 !! The keyword to search for.
93
94 character(1024) :: buffer2
95
96 1 if(present(keyword))then
97 buffer = buffer(index(buffer,keyword):)
98 end if
99
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 if(scan("=",buffer).ne.0) buffer2 = val(buffer)
100
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
101 1 found = found + 1
102 1 read(buffer2,*) variable
103 end if
104
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 end subroutine assignI
105 !###############################################################################
106
107
108 !###############################################################################
109 1 subroutine assignIvec(buffer, variable, found, keyword)
110 !! Assign an arbitrary length vector of integers to a variable.
111 implicit none
112
113 ! Arguments
114 integer, intent(inout) :: found
115 !! The number of variables found. External counter
116 character(*), intent(inout) :: buffer
117 !! The buffer to read from.
118 integer, dimension(:) :: variable
119 !! The variable to assign to.
120 character(*), optional, intent(in) :: keyword
121 !! The keyword to search for.
122
123 ! Local variables
124 integer :: i
125 !! Loop counter
126 character(1024) :: buffer2
127 !! Temporary buffer
128
129
130
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 if(present(keyword))then
131 buffer = buffer(index(buffer,keyword):)
132 end if
133
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 if(scan("=",buffer).ne.0) buffer2 = val(buffer)
134
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
135 1 found = found + 1
136
1/2
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
1 if(icount(buffer2).eq.1.and.&
137 icount(buffer2).ne.size(variable))then
138 read(buffer2,*) variable(1)
139 variable = variable(1)
140 else
141
3/4
✗ Branch 1 not taken.
✓ Branch 2 taken 4 times.
✓ Branch 3 taken 3 times.
✓ Branch 4 taken 1 times.
4 read(buffer2,*) ( variable(i), i = 1, size(variable) )
142 end if
143 end if
144
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 end subroutine assignIvec
145 !###############################################################################
146
147
148 !###############################################################################
149 9 subroutine assignR(buffer, variable, found, keyword)
150 !! Assign a float value to a variable.
151 implicit none
152
153 ! Arguments
154 integer, intent(inout) :: found
155 !! The number of variables found. External counter
156 character(*), intent(inout) :: buffer
157 !! The buffer to read from.
158 real(real32), intent(out) :: variable
159 !! The variable to assign to.
160 character(*), optional, intent(in) :: keyword
161 !! The keyword to search for.
162
163 ! Local variables
164 character(1024) :: buffer2
165 !! Temporary buffer
166
167 9 if(present(keyword))then
168 buffer = buffer(index(buffer,keyword):)
169 end if
170
1/2
✓ Branch 0 taken 9 times.
✗ Branch 1 not taken.
9 if(scan("=",buffer).ne.0) buffer2 = val(buffer)
171
2/4
✓ Branch 2 taken 9 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 9 times.
✗ Branch 5 not taken.
9 if(trim(adjustl(buffer2)).ne.'') then
172 9 found = found + 1
173 9 read(buffer2,*) variable
174 end if
175
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 9 times.
9 end subroutine assignR
176 !###############################################################################
177
178
179 !###############################################################################
180 8 subroutine assignRvec(buffer, variable, found, keyword)
181 !! Assign an arbitrary length float vector to a variable.
182 implicit none
183
184 ! Arguments
185 integer, intent(inout) :: found
186 !! The number of variables found. External counter
187 character(*), intent(inout) :: buffer
188 !! The buffer to read from.
189 real(real32), dimension(:), intent(out) :: variable
190 !! The variable to assign to.
191 character(*), optional, intent(in) :: keyword
192 !! The keyword to search for.
193
194 ! Local variables
195 integer :: i
196 !! Loop counter
197 character(1024) :: buffer2
198 !! Temporary buffer
199
200
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 8 times.
8 if(present(keyword))then
201 buffer = buffer(index(buffer,keyword):)
202 end if
203
1/2
✓ Branch 0 taken 8 times.
✗ Branch 1 not taken.
8 if(scan("=",buffer).ne.0) buffer2=val(buffer)
204
2/4
✓ Branch 2 taken 8 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 8 times.
✗ Branch 5 not taken.
8 if(trim(adjustl(buffer2)).ne.'') then
205 8 found = found + 1
206
1/2
✗ Branch 2 not taken.
✓ Branch 3 taken 8 times.
8 if(icount(buffer2).eq.1.and.&
207 icount(buffer2).ne.size(variable))then
208 read(buffer2,*) variable(1)
209 variable = variable(1)
210 else
211
3/4
✗ Branch 1 not taken.
✓ Branch 2 taken 33 times.
✓ Branch 3 taken 25 times.
✓ Branch 4 taken 8 times.
33 read(buffer2,*) (variable(i),i=1,size(variable))
212 end if
213 end if
214
1/2
✓ Branch 0 taken 8 times.
✗ Branch 1 not taken.
8 end subroutine assignRvec
215 !###############################################################################
216
217
218 !###############################################################################
219 1 subroutine assignS(buffer, variable, found, keyword)
220 !! Assign a string to a variable.
221 implicit none
222
223 ! Arguments
224 integer, intent(inout) :: found
225 !! The number of variables found. External counter
226 character(*), intent(inout) :: buffer
227 !! The buffer to read from.
228 character(*), intent(out) :: variable
229 !! The variable to assign to.
230 character(*), optional, intent(in) :: keyword
231 !! The keyword to search for.
232
233 ! Local variables
234 character(1024) :: buffer2
235 !! Temporary buffer
236
237 1 if(present(keyword))then
238
2/4
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
1 buffer = buffer(index(buffer,keyword):)
239 end if
240
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 if(scan("=",buffer).ne.0) buffer2 = val(buffer)
241
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
242 1 found = found + 1
243 1 read(buffer2,'(A)') variable
244 end if
245
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 end subroutine assignS
246 !###############################################################################
247
248
249 !###############################################################################
250 6 subroutine assignL(buffer, variable, found, keyword)
251 !! Assign a logical to a variable.
252 !!
253 !! This subroutine will assign a logical value to a variable. The
254 !! logical can take the form of a string or an integer. The following
255 !! are all valid logical values:
256 !! T, F, t, f, 1, 0
257 implicit none
258
259 ! Arguments
260 integer, intent(inout) :: found
261 !! The number of variables found. External counter
262 character(*), intent(inout) :: buffer
263 !! The buffer to read from.
264 logical, intent(out) :: variable
265 !! The variable to assign to.
266 character(*), optional, intent(in) :: keyword
267 !! The keyword to search for.
268
269 ! Local variables
270 character(1024) :: buffer2
271 !! Buffer to read from
272
273 6 if(present(keyword))then
274
2/4
✓ Branch 0 taken 6 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 6 times.
6 buffer=buffer(index(buffer,keyword):)
275 end if
276
1/2
✓ Branch 0 taken 6 times.
✗ Branch 1 not taken.
6 if(scan("=",buffer).ne.0) buffer2 = val(buffer)
277
2/4
✓ Branch 2 taken 6 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 6 times.
✗ Branch 5 not taken.
6 if(trim(adjustl(buffer2)).ne.'') then
278 6 found=found+1
279 if(index(buffer2,"T").ne.0.or.&
280
2/2
✓ Branch 0 taken 3 times.
✓ Branch 1 taken 3 times.
6 index(buffer2,"t").ne.0.or.&
281 index(buffer2,"1").ne.0) then
282 3 variable = .TRUE.
283 end if
284 if(index(buffer2,"F").ne.0.or.&
285
2/2
✓ Branch 0 taken 3 times.
✓ Branch 1 taken 3 times.
6 index(buffer2,"f").ne.0.or.&
286 index(buffer2,"0").ne.0) then
287 3 variable = .FALSE.
288 end if
289 end if
290
1/2
✓ Branch 0 taken 6 times.
✗ Branch 1 not taken.
6 end subroutine assignL
291 !###############################################################################
292
293
294 !###############################################################################
295 1 subroutine rm_comments(buffer, iline)
296 !! Remove comments from a buffer.
297 implicit none
298
299 ! Arguments
300 character(*), intent(inout) :: buffer
301 !! Buffer to remove comments from.
302 integer, optional, intent(in) :: iline
303 !! Line number.
304
305 ! Local variables
306 integer :: lbracket,rbracket
307 !! Bracketing variables
308 integer :: iline_
309 !! Line number
310
311 1 iline_ = 0
312 1 if(present(iline)) iline_ = iline
313
314
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))
315
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))
316
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 do while(scan(buffer,'(').ne.0.or.scan(buffer,')').ne.0)
317 lbracket = scan( buffer, '(', back=.true. )
318 rbracket = scan( buffer(lbracket:), ')' )
319 if( lbracket .eq. 0 .or. rbracket .eq. 0 )then
320 write(6,'(A,I0)') &
321 ' NOTE: a bracketing error was encountered on line ',iline_
322 buffer = ""
323 return
324 end if
325 rbracket = rbracket + lbracket - 1
326 buffer = buffer(:(lbracket-1)) // buffer((rbracket+1):)
327 end do
328
329
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 end subroutine rm_comments
330 !###############################################################################
331
332 end module raffle__tools_infile
333