Line data Source code
1 : !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
2 : !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
3 : !!!!
4 : !!!! MIT License
5 : !!!!
6 : !!!! ParaMonte: plain powerful parallel Monte Carlo library.
7 : !!!!
8 : !!!! Copyright (C) 2012-present, The Computational Data Science Lab
9 : !!!!
10 : !!!! This file is part of the ParaMonte library.
11 : !!!!
12 : !!!! Permission is hereby granted, free of charge, to any person obtaining a
13 : !!!! copy of this software and associated documentation files (the "Software"),
14 : !!!! to deal in the Software without restriction, including without limitation
15 : !!!! the rights to use, copy, modify, merge, publish, distribute, sublicense,
16 : !!!! and/or sell copies of the Software, and to permit persons to whom the
17 : !!!! Software is furnished to do so, subject to the following conditions:
18 : !!!!
19 : !!!! The above copyright notice and this permission notice shall be
20 : !!!! included in all copies or substantial portions of the Software.
21 : !!!!
22 : !!!! THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND,
23 : !!!! EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF
24 : !!!! MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT.
25 : !!!! IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM,
26 : !!!! DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR
27 : !!!! OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE
28 : !!!! OR THE USE OR OTHER DEALINGS IN THE SOFTWARE.
29 : !!!!
30 : !!!! ACKNOWLEDGMENT
31 : !!!!
32 : !!!! ParaMonte is an honor-ware and its currency is acknowledgment and citations.
33 : !!!! As per the ParaMonte library license agreement terms, if you use any parts of
34 : !!!! this library for any purposes, kindly acknowledge the use of ParaMonte in your
35 : !!!! work (education/research/industry/development/...) by citing the ParaMonte
36 : !!!! library as described on this page:
37 : !!!!
38 : !!!! https://github.com/cdslaborg/paramonte/blob/main/ACKNOWLEDGMENT.md
39 : !!!!
40 : !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
41 : !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
42 :
43 : !> \brief This module contains classes and procedures contents of external files.
44 : !> \author Amir Shahmoradi
45 :
46 : module FileContents_mod
47 :
48 : use JaggedArray_mod, only: CharVec_type
49 : use Err_mod, only: Err_type
50 : implicit none
51 :
52 : character(*), parameter :: MODULE_NAME = "@FileContents_mod"
53 :
54 : !> The FileContents_type class.
55 : type :: FileContents_type
56 : integer :: numRecord !< number f records (lines) in file.
57 : type(CharVec_type), allocatable :: Line(:) !< The list of lines in the file.
58 : type(Err_type) :: Err !< The error object.
59 : contains
60 : procedure, nopass :: getNumRecordInFile
61 : procedure, nopass :: getFileContents
62 : end type FileContents_type
63 :
64 : interface FileContents_type
65 : module procedure :: constructFileContents
66 : end interface FileContents_type
67 :
68 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
69 :
70 : contains
71 :
72 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
73 :
74 : !> \brief
75 : !> The constructor of the [FileContents_type](@ref filecontents_type) class.
76 : !>
77 : !> @param[in] filePath : The path to the file.
78 : !> @param[in] delEnabled : A logical flag indicating whether the file should be deleted upon return (**optional**, default = `.false.`).
79 : !>
80 : !> \return
81 : !> `FileContents` : An object of [FileContents_type](@ref filecontents_type) class.
82 21 : function constructFileContents(filePath,delEnabled) result(FileContents)
83 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
84 : !DEC$ ATTRIBUTES DLLEXPORT :: constructFileContents
85 : #endif
86 : implicit none
87 : character(*), intent(in) :: filePath
88 : logical , intent(in), optional :: delEnabled
89 : type(FileContents_type) :: FileContents
90 21 : call getFileContents(filePath,FileContents%Line,FileContents%numRecord,FileContents%Err,delEnabled)
91 21 : if (FileContents%Err%occurred) FileContents%Err%msg = "@constructFileContents()" // FileContents%Err%msg
92 21 : end function constructFileContents
93 :
94 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
95 :
96 : !> \brief
97 : !> Returns the entire content of a file as an array of strings.
98 : !>
99 : !> @param[in] path : The path to the file.
100 : !> @param[out] Contents : A list of lines in the file. Each array element corresponds to one line (record) in the file.
101 : !> @param[out] numRecord : The number of lines in the file.
102 : !> @param[out] Err : An object of [Err_type](@ref err_mod::err_type) indicating whether error has occurred during the file IO.
103 : !> @param[out] delEnabled : An optional logical value indicating whether the file should be deleted upon successful reading of it.
104 379 : subroutine getFileContents(path, Contents, numRecord, Err, delEnabled)
105 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
106 : !DEC$ ATTRIBUTES DLLEXPORT :: getFileContents
107 : #endif
108 21 : use JaggedArray_mod, only: CharVec_type
109 : use String_mod, only: num2str
110 : use Err_mod, only: Err_type
111 : implicit none
112 : character(len=*), intent(in) :: path
113 : type(CharVec_type), allocatable, intent(out) :: Contents(:)
114 : logical, intent(in), optional :: delEnabled
115 : type(Err_type), intent(out) :: Err
116 : integer, intent(out) :: numRecord
117 :
118 : character(99999) :: record
119 : integer :: fileUnit, irecord, i
120 : logical :: delEnabledDefault, isOpen, fileExists
121 :
122 : character(*), parameter :: PROCEDURE_NAME = MODULE_NAME//"@getFileContents()"
123 :
124 379 : Err%occurred = .false.
125 379 : Err%msg = ""
126 :
127 379 : delEnabledDefault = .false.
128 379 : if (present(delEnabled)) then
129 18 : delEnabledDefault = delEnabled
130 : end if
131 :
132 379 : call getNumRecordInFile(path,numRecord,Err)
133 379 : if (Err%occurred) then
134 : ! LCOV_EXCL_START
135 : Err%msg = PROCEDURE_NAME // Err%msg
136 : return
137 : end if
138 : ! LCOV_EXCL_STOP
139 :
140 12232 : allocate(Contents(numRecord))
141 :
142 : open( newunit = fileUnit & ! LCOV_EXCL_LINE
143 : , status = "old" & ! LCOV_EXCL_LINE
144 : , file = path & ! LCOV_EXCL_LINE
145 : #if defined INTEL_COMPILER_ENABLED && defined OS_IS_WINDOWS
146 : , SHARED & ! LCOV_EXCL_LINE
147 : #endif
148 379 : )
149 12232 : do irecord = 1,numRecord
150 11853 : read(fileUnit,"(A)", iostat=Err%stat) record
151 12232 : if (Err%stat==0) then
152 11853 : Contents(irecord)%record = trim(adjustl(record))
153 : ! LCOV_EXCL_START
154 : elseif (is_iostat_end(Err%stat)) then
155 : Err%occurred = .true.
156 : Err%msg = PROCEDURE_NAME // ": End-of-file error occurred while expecting " // &
157 : num2str(numRecord-irecord+1) // " records in file='" // path // "'."
158 : return
159 : elseif (is_iostat_eor(Err%stat)) then
160 : Err%occurred = .true.
161 : Err%msg = PROCEDURE_NAME // ": End-of-record error occurred while reading line number " // &
162 : num2str(irecord) // " from file='" // path // "'."
163 : return
164 : else
165 : Err%occurred = .true.
166 : Err%msg = PROCEDURE_NAME // ": Unknown error occurred while reading line number " // &
167 : num2str(irecord) // " from file='" // path // "'."
168 : return
169 : end if
170 : ! LCOV_EXCL_STOP
171 : end do
172 :
173 : ! attempt to delete the file repeatedly. This is important on windows systems as the file often remains locked.
174 :
175 379 : blockDeleteFile: if (delEnabledDefault) then
176 :
177 : ! Attempt to delete the file repeatedly
178 :
179 36 : loopDeleteFile: do i = 1, 100
180 36 : inquire(file=path, opened=isOpen, exist=fileExists, iostat = Err%stat)
181 36 : if (Err%stat==0) then
182 36 : if (fileExists) then
183 18 : if (.not. isOpen) then
184 : open( newunit = fileUnit & ! LCOV_EXCL_LINE
185 : , status = "replace" & ! LCOV_EXCL_LINE
186 : , iostat = Err%stat & ! LCOV_EXCL_LINE
187 : , file = path & ! LCOV_EXCL_LINE
188 : #if defined INTEL_COMPILER_ENABLED && defined OS_IS_WINDOWS
189 : , SHARED & ! LCOV_EXCL_LINE
190 : #endif
191 0 : )
192 : end if
193 18 : close(fileUnit, status="delete", iostat = Err%stat) ! parallel processes cannot delete the same file. Err%stat is required to handle exceptions.
194 : else
195 18 : return
196 : end if
197 : end if
198 : end do loopDeleteFile
199 :
200 : end if blockDeleteFile
201 :
202 : ! If file deletion fails or if it should not be deleted, then simply close the file and return.
203 :
204 361 : close(fileUnit, status = "keep", iostat = Err%stat) ! parallel processes cannot delete the same file. Err%stat is required to handle exceptions.
205 :
206 : !if (Err%stat>0) then
207 : !! LCOV_EXCL_START
208 : ! Err%occurred = .true.
209 : ! Err%msg = PROCEDURE_NAME // "Error occurred while attempting to close or delete the open file='" // path // "'."
210 : ! return
211 : !end if
212 : !! LCOV_EXCL_STOP
213 :
214 379 : end subroutine getFileContents
215 :
216 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
217 :
218 : !> \brief
219 : !> Returns the number of lines in a file.
220 : !>
221 : !> @param[in] filePath : The path to the file.
222 : !> @param[out] numRecord : The number of lines in the file.
223 : !> @param[out] Err : An object of [Err_type](@ref err_mod::err_type) indicating whether error has occurred during the file IO.
224 : !> @param[in] exclude : A string. If any line matches `exclude`, it will NOT be counted.
225 982 : subroutine getNumRecordInFile(filePath,numRecord,Err,exclude)
226 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
227 : !DEC$ ATTRIBUTES DLLEXPORT :: getNumRecordInFile
228 : #endif
229 379 : use Constants_mod, only: IK
230 : implicit none
231 : character(len=*), intent(in) :: filePath
232 : integer(IK) , intent(out) :: numRecord
233 : type(Err_type) , intent(out) :: Err
234 : character(*) , intent(in) , optional :: exclude
235 : character(len=1) :: record
236 : integer :: fileUnit
237 : logical :: fileExists, fileIsOpen, excludeIsPresent
238 : integer :: iostat
239 :
240 : character(*), parameter :: PROCEDURE_NAME = "@getNumRecordInFile()"
241 :
242 603 : Err%occurred = .false.
243 603 : Err%msg = ""
244 603 : excludeIsPresent = present(exclude)
245 :
246 : ! Check if file exists
247 : ! GFortran 7.3 bug: If file is not open, compiler assumes internal file if `number` is specified, causing runtime error.
248 :
249 603 : inquire( file=filePath, exist=fileExists, opened=fileIsOpen, number=fileUnit, iostat=Err%stat )
250 603 : if (Err%stat/=0) then
251 : ! LCOV_EXCL_START
252 : Err%occurred = .true.
253 : Err%msg = PROCEDURE_NAME // ": Error occurred while inquiring the status of file='" // filePath // "'."
254 : return
255 : end if
256 : ! LCOV_EXCL_STOP
257 :
258 603 : if (.not.fileExists) then
259 : ! LCOV_EXCL_START
260 : Err%occurred = .true.
261 : Err%msg = PROCEDURE_NAME // ": The input file='" // filePath // "' does not exist."
262 : return
263 : end if
264 : ! LCOV_EXCL_STOP
265 :
266 603 : if (fileIsOpen) close(unit=fileUnit,iostat=Err%stat)
267 603 : if (Err%stat>0) then
268 : ! LCOV_EXCL_START
269 : Err%occurred = .true.
270 : Err%msg = PROCEDURE_NAME // ": Error occurred while attempting to close the open input file='" // filePath // "'."
271 : return
272 : end if
273 : ! LCOV_EXCL_STOP
274 :
275 : open( newunit = fileUnit & ! LCOV_EXCL_LINE
276 : , iostat = Err%stat & ! LCOV_EXCL_LINE
277 : , file = filePath & ! LCOV_EXCL_LINE
278 : , status = "old" & ! LCOV_EXCL_LINE
279 : #if defined INTEL_COMPILER_ENABLED && defined OS_IS_WINDOWS
280 : , SHARED & ! LCOV_EXCL_LINE
281 : #endif
282 603 : )
283 603 : if (Err%stat>0) then
284 : ! LCOV_EXCL_START
285 : Err%occurred = .true.
286 : Err%msg = PROCEDURE_NAME // ": Error occurred while opening input file='" // filePath // "'."
287 : return
288 : end if
289 : ! LCOV_EXCL_STOP
290 :
291 603 : numRecord = 0_IK
292 302399 : do
293 303002 : read(fileUnit,'(A)',iostat=iostat) record
294 303002 : if(iostat==0) then
295 302399 : if (excludeIsPresent) then
296 42004 : if (trim(adjustl(record))/=exclude) numRecord = numRecord + 1_IK
297 : else
298 260395 : numRecord = numRecord + 1_IK
299 : end if
300 302399 : cycle
301 603 : elseif(is_iostat_end(iostat) .or. is_iostat_eor(iostat)) then
302 603 : exit
303 : ! LCOV_EXCL_START
304 : else
305 : Err%occurred = .true.
306 : Err%stat = iostat
307 : Err%msg = PROCEDURE_NAME // ": Error occurred while reading input file='" // filePath // "'."
308 : return
309 : end if
310 : ! LCOV_EXCL_STOP
311 : end do
312 :
313 603 : close(fileUnit,iostat=Err%stat)
314 603 : if (Err%stat>0) then
315 : ! LCOV_EXCL_START
316 : Err%occurred = .true.
317 : Err%msg = PROCEDURE_NAME // ": Error occurred while attempting to close the open input file='" // &
318 : filePath // "' after counting the number of records in file."
319 : return
320 : end if
321 : ! LCOV_EXCL_STOP
322 :
323 603 : end subroutine getNumRecordInFile
324 :
325 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
326 :
327 : end module FileContents_mod ! LCOV_EXCL_LINE
|