Soil Water Balance (SWB2)
Loading...
Searching...
No Matches
file_operations.F90
Go to the documentation of this file.
2
3 use iso_c_binding, only : c_int, c_float, c_double, c_bool
4 use iso_fortran_env, only : iostat_end
5 use logfiles
6 use exceptions
8 use fstring
10 implicit none
11
12 private
13
15
16 integer (c_int), parameter :: max_str_len = 65536
17
18 type, public :: ascii_file_t
19
20 character (len=:), allocatable :: sfilename
21 character (len=:), allocatable :: sdelimiters
22 character (len=:), allocatable :: scommentchars
23 type (fstring_list_t) :: slcolnames
24 logical (c_bool) :: remove_extra_delimiters = false
25 integer (c_int) :: icurrentlinenum = 0
26 integer (c_int) :: inumberoflines = 0
27 integer (c_int) :: inumberofrecords = 0
28 integer (c_int) :: inumberofheaderlines = 1
29 logical (c_bool) :: lisopen = false
30 logical (c_bool) :: lreadonly = true
31 logical (c_bool) :: leof = false
32 integer (c_int) :: iunitnum
33 integer (c_int) :: istat
34 character (len=MAX_STR_LEN) :: sbuf
35 character (len=:), allocatable :: stmissingvalue
36
37 contains
38
39 procedure, private :: open_file_read_access_sub
40 procedure, private :: open_file_write_access_sub
41 generic :: open => open_file_read_access_sub, &
43
44 procedure, private :: close_file_sub
45 generic :: close => close_file_sub
46
47 procedure, private :: is_file_open_fn
48 generic :: isopen => is_file_open_fn
49
50 procedure, private :: have_we_reached_the_eof_fn
51 generic :: iseof => have_we_reached_the_eof_fn
52
53 procedure, private :: does_file_exist_fn
54 generic :: exists => does_file_exist_fn
55
56 procedure, private :: is_current_line_a_comment_fn
57 generic :: iscomment => is_current_line_a_comment_fn
58
59 procedure, private :: count_number_of_lines_sub
60 generic :: countlines => count_number_of_lines_sub
61
62 procedure, private :: return_num_lines_fn
63 generic :: numlines => return_num_lines_fn
64
65 procedure, private :: return_num_records_fn
66 generic :: numrecords => return_num_records_fn
67
68 procedure, private :: return_current_linenum_fn
69 generic :: currentlinenum => return_current_linenum_fn
70
71 procedure, private :: return_fortran_unit_number_fn
73
74 procedure, private :: read_header_fn
75 generic, public :: readheader => read_header_fn
76
77 procedure, private :: read_line_of_data_fn
78 generic, public :: readline => read_line_of_data_fn
79
80 procedure, private :: write_line_of_data_sub
81 generic, public :: writeline => write_line_of_data_sub
82
83 end type ascii_file_t
84
85contains
86
87 function return_fortran_unit_number_fn(this) result(iUnitNum)
88
89 class(ascii_file_t) :: this
90 integer (c_int) :: iunitnum
91
92 iunitnum = this%iUnitNum
93
95
96!--------------------------------------------------------------------------------------------------
97
98 function return_num_lines_fn(this) result(iNumLines)
99
100 class(ascii_file_t) :: this
101 integer (c_int) :: inumlines
102
103 inumlines = this%iNumberOfLines
104
105 end function return_num_lines_fn
106
107!--------------------------------------------------------------------------------------------------
108
109 function return_num_records_fn(this) result(iNumRecords)
110
111 class(ascii_file_t) :: this
112 integer (c_int) :: inumrecords
113
114 inumrecords = this%iNumberOfRecords
115
116 end function return_num_records_fn
117
118!--------------------------------------------------------------------------------------------------
119
120 function return_current_linenum_fn(this) result(iCurrentLinenum)
121
122 class(ascii_file_t) :: this
123 integer (c_int) :: icurrentlinenum
124
125 icurrentlinenum = this%iCurrentLinenum
126
127 end function return_current_linenum_fn
128
129!--------------------------------------------------------------------------------------------------
130
131 function have_we_reached_the_eof_fn(this) result(lIsEOF)
132
133 class(ascii_file_t) :: this
134 logical (c_bool) :: liseof
135
136 liseof = this%lEOF
137
138 end function have_we_reached_the_eof_fn
139
140!--------------------------------------------------------------------------------------------------
141
142 function is_current_line_a_comment_fn(this) result(lIsComment)
143
144 class(ascii_file_t) :: this
145 logical (c_bool) :: liscomment
146
147 ! [ LOCALS ]
148 integer (c_int) :: iindex
149 integer (c_int) :: ilen
150 character (len=1) :: sbuftemp
151
152 ilen = len_trim( this%sBuf )
153
154 sbuftemp = adjustl(this%sBuf)
155
156 iindex = verify( sbuftemp , this%sCommentChars )
157
158 liscomment = false
159
160 if ( iindex == 0 .or. len_trim(this%sBuf) == 0 ) liscomment = true
161
163
164!--------------------------------------------------------------------------------------------------
165
166 subroutine open_file_read_access_sub(this, sFilename, sCommentChars, sDelimiters, lHasHeader )
167
168 class(ascii_file_t), intent(inout) :: this
169 character (len=*), intent(in) :: sfilename
170 character (len=*), intent(in) :: scommentchars
171 character (len=*), intent(in) :: sdelimiters
172 logical (c_bool), intent(in), optional :: lhasheader
173
174 ! [ LOCALS ]
175 character (len=len(sFilename) ) :: sfilename_l
176
177 ! 'fix_pathname' simply replaces forward slashes and backslashes with whatever the native OS
178 ! path delimiter character should be
179 sfilename_l = fix_pathname( sfilename )
180
181 this%sCommentChars = scommentchars
182 this%sDelimiters = sdelimiters
183
184 if (present( lhasheader ) ) then
185 if (.not. lhasheader ) this%iNumberOfHeaderLines = 0
186 endif
187
188 if ( this%isOpen() ) then
189
190 call die( "PROGRAMMING ERROR--file already open: "//dquote( fully_qualified_filename( sfilename_l ) )//"." )
191
192 else
193
194 open(newunit=this%iUnitNum, file=fully_qualified_filename( sfilename_l ), iostat=this%iStat, action='READ')
195 call assert(this%iStat == 0, "Failed to open file "//dquote( fully_qualified_filename( sfilename_l ) )//"." &
196 //" Exit code: "//ascharacter( this%iStat )//".", __file__, __line__)
197
198 this%lIsOpen = true
199 this%lEOF = false
200
201 call this%countLines()
202
203 call logs%write( smessage="Opened file "//dquote( fully_qualified_filename( sfilename_l ) ), itab=22, &
204 ilinesbefore=1, iloglevel=log_all )
205 call logs%write( "Comment characters: "//dquote(scommentchars), itab=42 )
206 call logs%write( "Number of lines in file: "//ascharacter( this%numLines() ), itab=37 )
207 call logs%write( "Number of lines excluding blanks, headers and comments: " &
208 //ascharacter( this%numRecords() ), itab=6 )
209
210 endif
211
212 end subroutine open_file_read_access_sub
213
214!--------------------------------------------------------------------------------------------------
215
216 subroutine open_file_write_access_sub(this, sFilename, lQuiet )
217
218 class(ascii_file_t), intent(inout) :: this
219 character (len=*), intent(in) :: sfilename
220 logical (c_bool), intent(in), optional :: lquiet
221
222 ! [ LOCALS ]
223 logical :: lquiet_l
224 character (len=len(sFilename) ) :: sfilename_l
225
226 sfilename_l = fix_pathname( sfilename )
227
228 if ( present( lquiet ) ) then
229 lquiet_l = lquiet
230 else
231 lquiet_l = false
232 endif
233
234 if (.not. this%isOpen() ) then
235
236 open(newunit=this%iUnitNum, file=sfilename_l, iostat=this%iStat, action='WRITE')
237 call assert(this%iStat == 0, "Failed to open file "//dquote(sfilename_l)//".", __file__, __line__)
238
239 this%lIsOpen = true
240 this%lEOF = false
241 this%lReadOnly = false
242 this%sFilename = trim(sfilename_l)
243
244 if ( .not. lquiet_l ) &
245 call logs%write( "Opened file with write access: "//dquote(sfilename_l))
246
247 else
248 call logs%write( "Failed to open file "//dquote(sfilename_l)//" with WRITE access" )
249 endif
250
251 end subroutine open_file_write_access_sub
252
253!--------------------------------------------------------------------------------------------------
254
255 subroutine close_file_sub(this)
256
257 class(ascii_file_t) :: this
258
259 integer (c_int) :: istat
260
261 close(unit=this%iUnitNum, iostat=this%iStat)
262
263 this%lIsOpen = false
264
265 end subroutine close_file_sub
266
267!--------------------------------------------------------------------------------------------------
268
269 function does_file_exist_fn(this, sFilename) result(lExists)
270
271 class(ascii_file_t) :: this
272 character (len=*), intent(in) :: sfilename
273 logical(c_bool) :: lexists
274
275 inquire(file=fully_qualified_filename( sfilename ), exist=lexists)
276
277 end function does_file_exist_fn
278
279!--------------------------------------------------------------------------------------------------
280
281 function is_file_open_fn(this) result(lIsOpen)
282
283 class(ascii_file_t) :: this
284 logical(c_bool) :: lisopen
285
286 lisopen = this%lIsOpen
287
288 end function is_file_open_fn
289
290!--------------------------------------------------------------------------------------------------
291
293
294 class(ascii_file_t), intent(inout) :: this
295
296 ! [ LOCALS ]
297 integer (c_int) :: istat
298 integer (c_int) :: inumlines
299 integer (c_int) :: inumrecords
300 integer (c_int) :: iindex
301
302 inumlines = 0
303 inumrecords = 0
304 istat = 0
305
306 if ( this%isOpen() ) then
307
308 rewind( unit = this%iUnitNum )
309
310 do
311
312 read (unit = this%iUnitNum, fmt="(a)", iostat = istat) this%sBuf
313
314 if (istat == iostat_end) exit
315
316 inumlines = inumlines + 1
317
318 if ( .not. this%isComment() ) inumrecords = inumrecords + 1
319
320 enddo
321
322 rewind( unit = this%iUnitNum )
323
324 this%iNumberOfLines= inumlines
325 this%iNumberOfRecords = inumrecords - this%iNumberOfHeaderLines
326
327 endif
328
329 end subroutine count_number_of_lines_sub
330
331!--------------------------------------------------------------------------------------------------
332
333 function read_header_fn(this) result (stList)
334
335 class(ascii_file_t), intent(inout) :: this
336 type (fstring_list_t) :: stlist
337
338 ! [ LOCALS ]
339 character (len=MAX_STR_LEN) :: sstring
340 character (len=MAX_STR_LEN) :: ssubstring
341 character (len=MAX_STR_LEN) :: ssubstringclean
342 integer (c_int) :: istat
343
344 this%sBuf = this%readline()
345 call stlist%clear()
346
347 do while ( len_trim( this%sBuf ) > 0)
348
349 call chomp( str=this%sBuf, substr=ssubstring, delimiter_chr=this%sDelimiters, &
350 remove_extra_delimiters=this%remove_extra_delimiters )
351
352 call replace(ssubstring, " ", "_")
353 call replace(ssubstring, ".", "_")
354 ssubstringclean = trim( clean( ssubstring, double_quote ) )
355 call stlist%append( trim( adjustl( ssubstringclean ) ) )
356
357 enddo
358
359 end function read_header_fn
360
361!--------------------------------------------------------------------------------------------------
362
363 subroutine write_line_of_data_sub( this, sText )
364
365 class(ascii_file_t), intent(inout) :: this
366 character (len=*), intent(in) :: sText
367
368 ! [ LOCALS ]
369 integer (c_int) :: iStat
370
371 call assert( .not. this%lReadOnly, "INTERNAL ERROR -- File " &
372 //dquote( fully_qualified_filename( this%sFilename ) ) &
373 //" was opened as READONLY.", __file__, __line__ )
374
375 if (this%isOpen() ) then
376
377 write ( unit = this%iUnitNum, fmt = "(a)", iostat = istat ) trim(stext)
378
379 endif
380
381 end subroutine write_line_of_data_sub
382
383!--------------------------------------------------------------------------------------------------
384
385 function read_line_of_data_fn(this) result(sText)
386
387 class(ascii_file_t), intent(inout) :: this
388 character (len=:), allocatable :: stext
389
390 ! [ LOCALS ]
391 integer (c_int) :: istat
392 logical (c_bool) :: liscomment
393
394 liscomment = true
395
396 do while ( liscomment .and. this%isOpen() )
397
398 if (this%isOpen() ) then
399
400 read (unit = this%iUnitNum, fmt = "(a)", iostat = istat) this%sBuf
401
402 if (istat == iostat_end) then
403 this%lEOF = true
404 stext = ""
405 call this%close()
406 else
407 stext = trim(this%sBuf)
408 this%iCurrentLinenum = this%iCurrentLinenum + 1
409 endif
410
411 liscomment = this%isComment()
412
413 endif
414
415 enddo
416
417 end function read_line_of_data_fn
418
419!--------------------------------------------------------------------------------------------------
420
421 function fully_qualified_filename( filename, pathname )
422
423 character(len=*), intent(in) :: filename
424 character(len=*), intent(in), optional :: pathname
425 character(len=:), allocatable :: fully_qualified_filename
426
427 if (.not. present(pathname) ) then
428
430
431 else
432
433 fully_qualified_filename = trim( pathname )//fix_pathname(filename)
434
435 endif
436
437 end function fully_qualified_filename
438
439
440end module file_operations
This module contains physical constants and convenience functions aimed at performing unit conversion...
character(len=len_trim(input_pathname)) function fix_pathname(input_pathname)
logical(c_bool), parameter, public true
logical(c_bool), parameter, public false
subroutine, public die(smessage, smodule, iline, shints, scalledby, icalledbyline)
subroutine count_number_of_lines_sub(this)
type(fstring_list_t) function read_header_fn(this)
subroutine open_file_write_access_sub(this, sfilename, lquiet)
character(len=:) function, allocatable, public fully_qualified_filename(filename, pathname)
character(len=:) function, allocatable read_line_of_data_fn(this)
logical(c_bool) function is_file_open_fn(this)
subroutine close_file_sub(this)
integer(c_int), parameter max_str_len
subroutine write_line_of_data_sub(this, stext)
integer(c_int) function return_num_records_fn(this)
logical(c_bool) function have_we_reached_the_eof_fn(this)
integer(c_int) function return_num_lines_fn(this)
logical(c_bool) function is_current_line_a_comment_fn(this)
subroutine open_file_read_access_sub(this, sfilename, scommentchars, sdelimiters, lhasheader)
integer(c_int) function return_current_linenum_fn(this)
integer(c_int) function return_fortran_unit_number_fn(this)
logical(c_bool) function does_file_exist_fn(this, sfilename)
character(len=1), parameter, public double_quote
Definition fstring.F90:177
type(logfile_t), public logs
Definition logfiles.F90:62