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 to obtain a list of files in a given directory.
44 : !> \author Amir Shahmoradi
45 :
46 : module FileList_mod
47 :
48 : use String_mod, only: CharVec_type
49 : use Constants_mod, only: IK, RK
50 : use Err_mod, only: Err_type
51 : implicit none
52 :
53 : public
54 :
55 : character(*), parameter :: MODULE_NAME = "@FileList_mod"
56 :
57 : !> The FileList_type class.
58 : type :: FileList_type
59 : character(:), allocatable :: searchStr
60 : character(:), allocatable :: orderStr
61 : character(:), allocatable :: excludeStr
62 : integer(IK) :: count
63 : type(CharVec_type), allocatable :: File(:)
64 : type(Err_type) :: Err
65 : contains
66 : procedure, nopass :: get => getFileList
67 : end type FileList_type
68 :
69 : interface FileList_type
70 : module procedure :: constructFileList
71 : end interface FileList_type
72 :
73 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
74 :
75 : contains
76 :
77 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
78 :
79 : !> The constructor of the [FileList_type](@ref filelist_type) class.
80 : !> @param[in] searchStr : The pattern for the file search (**optional**).
81 : !> @param[in] orderStr : The order by which the search results will be listed (**optional**, default = "name").
82 : !> @param[in] excludeStr : The string which the listed files should not contain (**optional**, default = "").
83 : !> @param[in] OS : An object of class [OS_type](@ref system_mod::os_type) indicating the OS type (**optional**).
84 : !>
85 : !> \return
86 : !> FileList : An object of [FileList_type](@ref filelist_type) class.
87 24 : function constructFileList(searchStr,orderStr,excludeStr,OS) result(FileList)
88 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
89 : !DEC$ ATTRIBUTES DLLEXPORT :: constructFileList
90 : #endif
91 : use System_mod, only: OS_type
92 : implicit none
93 : character(*), intent(in), optional :: searchStr
94 : character(*), intent(in), optional :: excludeStr
95 : character(*), intent(in), optional :: orderStr
96 : type(OS_type), intent(inout), optional :: OS
97 : type(FileList_type) :: FileList
98 24 : if (present(searchStr)) then
99 3 : FileList%searchStr = searchStr
100 : else
101 21 : FileList%searchStr = ""
102 : end if
103 24 : if (present(orderStr)) then
104 9 : FileList%orderStr = orderStr
105 : else
106 15 : FileList%orderStr = ""
107 : end if
108 24 : if (present(excludeStr)) then
109 3 : FileList%excludeStr = excludeStr
110 : else
111 21 : FileList%excludeStr = ""
112 : end if
113 24 : call getFileList(FileList%File,FileList%Err,FileList%count,FileList%searchStr,FileList%orderStr,FileList%excludeStr,OS)
114 24 : end function constructFileList
115 :
116 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
117 :
118 : !> Return a list of files that match `searchStr`.
119 : !> @param[out] FileList : The list of files matching the requested search pattern (**optional**).
120 : !> @param[out] count : The number of files (**optional**).
121 : !> @param[out] Err : The error object indicating the occurrence of error.
122 : !> @param[in] searchStr : The pattern for the file search (**optional**). It can be the path of the folder of interest to be searched.
123 : !> @param[in] orderStr : The order by which the search results will be listed (**optional**, default = "name").
124 : !> @param[in] excludeStr : The string which the listed files should not contain (**optional**, default = "").
125 : !> @param[in] OS : An object of class [OS_type](@ref system_mod::os_type) indicating the OS type (**optional**).
126 : !>
127 : !> \return
128 : !> FileList : An object of [FileList_type](@ref filelist_type) class.
129 27 : subroutine getFileList(FileList,Err,count,searchStr,orderStr,excludeStr,OS)
130 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
131 : !DEC$ ATTRIBUTES DLLEXPORT :: getFileList
132 : #endif
133 :
134 : use, intrinsic :: iso_fortran_env, only: output_unit
135 24 : use System_mod, only: OS_type, executeCmd, sleep !, removeFile
136 : use Constants_mod, only: IK, RK, MAX_REC_LEN
137 : use String_mod, only: getLowerCase, num2str
138 : use JaggedArray_mod, only: CharVec_type
139 : use DateTime_mod, only: DateTime_type
140 : use Err_mod, only: Err_type
141 :
142 : implicit none
143 :
144 : character(*), intent(in), optional :: searchStr, orderStr, excludeStr
145 : type(CharVec_type), allocatable, intent(out) :: FileList(:)
146 : type(Err_type), intent(out) :: Err
147 : integer(IK), intent(out), optional :: count
148 : type(OS_type), intent(inout), optional :: OS
149 :
150 27 : character(:), allocatable :: search,order,exclude !,searchModified
151 27 : character(:), allocatable :: command,filename,stdErr,recordTrimmed
152 : character(MAX_REC_LEN) :: record
153 : integer(IK) :: fileUnit
154 : integer(IK) :: counter,nrecord,nskip,fileCounter
155 : logical :: fileIsOpen, isWindowsShell
156 :
157 : character(*), parameter :: PROCEDURE_NAME = "@getFileList()"
158 :
159 27 : Err%occurred = .false.
160 27 : Err%msg = ""
161 :
162 27 : if (present(searchStr)) then
163 24 : search = trim(adjustl(searchStr))
164 : else
165 3 : search = ""
166 : end if
167 :
168 27 : if (present(orderStr)) then
169 24 : if ( trim(adjustl(orderStr))/="" ) then
170 9 : order = getLowerCase( trim(adjustl(orderStr) ))
171 : else
172 15 : order = "name"
173 : end if
174 : else
175 3 : order = "name"
176 : end if
177 :
178 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
179 : ! check if the input order request is supported
180 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
181 :
182 27 : if (order/="name" .and. order/="date") then
183 3 : Err%occurred = .true.
184 3 : Err%msg = PROCEDURE_NAME // ": Error Occurred. The requested search order orderStr='" // order // "' is not supported."
185 3 : return
186 : end if
187 :
188 24 : if (present(excludeStr)) then
189 21 : exclude = trim(adjustl(excludeStr))
190 : else
191 3 : exclude = ""
192 : end if
193 :
194 24 : if (present(OS)) then
195 3 : if ( OS%isWindows .and. .not. (OS%Shell%isCMD .or. OS%Shell%isPowershell) ) then
196 : ! LCOV_EXCL_START
197 : call OS%Shell%query()
198 : if (OS%Shell%Err%occurred) then
199 : Err = OS%Shell%Err
200 : Err%msg = PROCEDURE_NAME//": Error occurred while attempting to query OS type in search of files containing '"//search//"'.\n"//Err%msg
201 : return
202 : end if
203 : end if
204 : isWindowsShell = OS%isWindows .and. .not. OS%Shell%isUnix
205 : ! LCOV_EXCL_STOP
206 : else
207 : block
208 21 : type(OS_type) :: OS
209 21 : call OS%query(shellQueryEnabled = .true.)
210 21 : if (OS%Err%occurred) then
211 : ! LCOV_EXCL_START
212 : Err = OS%Err
213 : ! LCOV_EXCL_STOP
214 21 : elseif (OS%Shell%Err%occurred) then
215 : ! LCOV_EXCL_START
216 : Err = OS%Shell%Err
217 : ! LCOV_EXCL_STOP
218 : end if
219 21 : if (Err%occurred) then
220 : ! LCOV_EXCL_START
221 : Err%msg = PROCEDURE_NAME//": Error occurred while attempting to query OS type in search of files containing '"//search//"'.\n"//Err%msg
222 : return
223 : ! LCOV_EXCL_STOP
224 : end if
225 21 : isWindowsShell = OS%isWindows .and. .not. OS%Shell%isUnix
226 : end block
227 : end if
228 :
229 24 : if (isWindowsShell) then
230 :
231 : !call winify(search,searchModified,Err)
232 : !if (Err%occurred) then
233 : ! Err%msg = PROCEDURE_NAME // ": Error occurred while attempting to modify searchStr='" // search // &
234 : ! "' according to the OS type.\n" // Err%msg
235 : ! return
236 : !end if
237 :
238 : ! see: https://www.computerhope.com/dirhlp.htm
239 : ! /b Uses bare format (no heading information or summary).
240 : ! /A[:Attributes] List only files with the specified file attributes. Attributes is a series of letters:
241 : ! D : Directories.
242 : ! R : Read-only files.
243 : ! H : Hidden files.
244 : ! A : Files ready for archiving.
245 : ! S : System files.
246 : ! - : Prefix meaning "not".
247 : ! /O[:SortOrder] List files in sorted order, indicated by SortOrder:
248 : ! N : By name (alphabetic).
249 : ! S : By size (smallest first).
250 : ! E : By extension (alphabetic).
251 : ! D : By date and time (earliest first).
252 : ! G : Group directories first.
253 : ! - : Prefix to reverse order.
254 : ! A : By Last Access Date (earliest first).
255 :
256 0 : if (order=="name") then ! ascending in name
257 0 : command = "dir /b /a-d " // search
258 0 : elseif (order=="date") then ! newest will be first
259 0 : command = "dir /b /a-d /o:-d " // search
260 : end if
261 0 : if ( len(exclude)>0 ) command = command // " | findstr /v /i " // exclude
262 :
263 : else ! It is not windows: either Mac or Linux
264 :
265 : ! Assume Bash environment:
266 : ! see: http://pubs.opengroup.org/onlinepubs/9699919799/utilities/ls.html
267 : ! 1 causes each file to be printed on one line
268 : ! p causes directories to have "/" at the end
269 : ! t sorts files by modification date, most recent first.
270 : ! r reverses the sort order (not present here)
271 :
272 24 : if (order=="name") then ! ascending in name
273 : !command = "ls -1 " // searchModified
274 21 : command = "ls -1p " // search
275 3 : elseif (order=="date") then ! newest will be first
276 3 : command = "ls -1pt " // search
277 : end if
278 27 : if ( len(exclude)>0 ) command = command // " --ignore=" // trim(adjustl(exclude))
279 :
280 : end if
281 :
282 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
283 : ! generate a brand new, non-existing filename
284 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
285 :
286 : block
287 : use System_mod, only: RandomFileName_type
288 24 : type(RandomFileName_type) :: RFN
289 24 : RFN = RandomFileName_type(key="getFileList")
290 24 : if (RFN%Err%occurred) then
291 : ! LCOV_EXCL_START
292 : RFN%Err%msg = PROCEDURE_NAME // RFN%Err%msg
293 : return
294 : end if
295 : ! LCOV_EXCL_STOP
296 48 : filename = RFN%path
297 : end block
298 24 : stdErr = filename // ".stderr"
299 :
300 24 : call executeCmd( command = command//" > "//filename//" 2> "//stdErr, Err=Err )
301 24 : if (Err%occurred) then
302 : ! LCOV_EXCL_START
303 : Err%msg = PROCEDURE_NAME // ": Error occurred while attempting to write the search results to external file.\n" // Err%msg
304 : return
305 : end if
306 : ! LCOV_EXCL_STOP
307 :
308 : ! delete the stderr file
309 :
310 : open( newunit = fileUnit & ! LCOV_EXCL_LINE
311 : , status = "replace" & ! LCOV_EXCL_LINE
312 : , file = stdErr & ! LCOV_EXCL_LINE
313 : #if defined INTEL_COMPILER_ENABLED && defined OS_IS_WINDOWS
314 : , SHARED & ! LCOV_EXCL_LINE
315 : #endif
316 24 : )
317 24 : close(fileUnit, status = "delete", iostat = Err%stat) ! parallel processes cannot delete the same file
318 :
319 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
320 : ! now count the number of records in file:
321 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
322 :
323 24 : inquire(file=filename,opened=fileIsOpen,number=fileUnit,iostat=Err%stat) ! check if the file already exists
324 24 : if (Err%stat/=0) then
325 : ! LCOV_EXCL_START
326 : Err%occurred = .true.
327 : Err%msg = PROCEDURE_NAME // ": Error occurred while inquiring the open status of file='" // filename // "'."
328 : return
329 : end if
330 : ! LCOV_EXCL_STOP
331 :
332 24 : if (fileIsOpen) close(fileUnit,iostat=Err%stat)
333 : ! LCOV_EXCL_START
334 : if (Err%stat/=0) then
335 : Err%occurred = .true.
336 : Err%msg = PROCEDURE_NAME // ": Error occurred while attempting to close the open file='" // filename // "'."
337 : return
338 : end if
339 : ! LCOV_EXCL_STOP
340 :
341 24 : call sleep(seconds=0.1_RK,Err=Err)
342 : ! LCOV_EXCL_START
343 : if (Err%occurred) then
344 : Err%msg = PROCEDURE_NAME // Err%msg
345 : return
346 : end if
347 : ! LCOV_EXCL_STOP
348 :
349 : ! open the list file
350 :
351 : open( newunit = fileUnit & ! LCOV_EXCL_LINE
352 : , iostat = Err%stat & ! LCOV_EXCL_LINE
353 : , file = filename & ! LCOV_EXCL_LINE
354 : , status = "old" & ! LCOV_EXCL_LINE
355 : #if defined INTEL_COMPILER_ENABLED && defined OS_IS_WINDOWS
356 : , SHARED & ! LCOV_EXCL_LINE
357 : #endif
358 24 : )
359 : ! LCOV_EXCL_START
360 : if (Err%stat>0) then
361 : Err%occurred = .true.
362 : Err%msg = PROCEDURE_NAME // ": Unknown error occurred while opening file='" // filename // "'."
363 : return
364 : end if
365 : ! LCOV_EXCL_STOP
366 :
367 24 : nskip = 0 ! check filename is not among records
368 24 : nrecord = 0 ! number of filenames in the file
369 205 : do
370 229 : read(fileUnit,"(A)",iostat=Err%stat) record
371 229 : if ( is_iostat_eor(Err%stat) ) then
372 : ! LCOV_EXCL_START
373 : Err%occurred = .true.
374 : Err%msg = PROCEDURE_NAME // ": End-Of-Record error condition occurred while attempting to read from file='" // filename // "'."
375 : return
376 : ! LCOV_EXCL_STOP
377 229 : elseif ( is_iostat_end(Err%stat) ) then
378 24 : exit
379 205 : elseif ( Err%stat>0 ) then
380 : ! LCOV_EXCL_START
381 : Err%occurred = .true.
382 : Err%msg = PROCEDURE_NAME // ": Unknown error condition occurred while attempting to read from file='" // filename // "'."
383 : return
384 : ! LCOV_EXCL_STOP
385 : else
386 205 : recordTrimmed = trim(adjustl(record))
387 205 : if(filename==recordTrimmed) nskip = nskip + 1
388 205 : nrecord = nrecord + 1
389 205 : cycle
390 : end if
391 : end do
392 24 : close(fileUnit, iostat = Err%stat)
393 24 : if (Err%stat/=0) then
394 : ! LCOV_EXCL_START
395 : Err%occurred = .true.
396 : Err%msg = PROCEDURE_NAME // ": Error occurred while attempting to close the open file='" // filename // "'."
397 : return
398 : end if
399 : ! LCOV_EXCL_STOP
400 :
401 208 : allocate(FileList(nrecord-nskip))
402 :
403 24 : call sleep(seconds=0.1_RK,Err=Err)
404 24 : if (Err%occurred) then
405 : ! LCOV_EXCL_START
406 : Err%msg = PROCEDURE_NAME // Err%msg
407 : return
408 : end if
409 : ! LCOV_EXCL_STOP
410 :
411 : open( newunit = fileUnit & ! LCOV_EXCL_LINE
412 : , iostat = Err%stat & ! LCOV_EXCL_LINE
413 : , file = filename & ! LCOV_EXCL_LINE
414 : , status = "old" & ! LCOV_EXCL_LINE
415 : #if defined INTEL_COMPILER_ENABLED && defined OS_IS_WINDOWS
416 : , SHARED & ! LCOV_EXCL_LINE
417 : #endif
418 24 : )
419 24 : if (Err%stat>0) then
420 : ! LCOV_EXCL_START
421 : Err%occurred = .true.
422 : Err%msg = PROCEDURE_NAME // ": Unknown error occurred while opening file='" // filename // "'."
423 : return
424 : end if
425 : ! LCOV_EXCL_STOP
426 :
427 24 : fileCounter = 0
428 229 : do counter = 1,nrecord
429 205 : read(fileUnit,"(A)",iostat=Err%stat) record
430 205 : if ( is_iostat_eor(Err%stat) ) then
431 : ! LCOV_EXCL_START
432 : Err%occurred = .true.
433 : Err%msg = PROCEDURE_NAME // ": End-Of-Record error condition occurred while attempting to read from file='" // filename // "'."
434 : return
435 : ! LCOV_EXCL_STOP
436 205 : elseif ( is_iostat_end(Err%stat) ) then
437 0 : exit
438 205 : elseif ( Err%stat>0 ) then
439 : ! LCOV_EXCL_START
440 : Err%occurred = .true.
441 : Err%msg = PROCEDURE_NAME // ": Unknown error condition occurred while attempting to read from file='" // filename // "'."
442 : return
443 : end if
444 : ! LCOV_EXCL_STOP
445 205 : recordTrimmed = trim(adjustl(record))
446 229 : if(filename/=recordTrimmed) then
447 184 : fileCounter = fileCounter + 1
448 184 : FileList(fileCounter)%record = trim(adjustl(record))
449 : end if
450 : end do
451 :
452 24 : if (present(count)) count = fileCounter
453 :
454 24 : close(fileUnit, status = "delete", iostat = Err%stat) ! parallel processes cannot delete the same file
455 :
456 : !if (Err%stat/=0) then
457 : !! LCOV_EXCL_START
458 : ! Err%occurred = .true.
459 : ! Err%msg = PROCEDURE_NAME // ": Error occurred while attempting to close the open file='" // filename // "'."
460 : ! return
461 : !end if
462 : !! LCOV_EXCL_STOP
463 :
464 : ! remove the files
465 : !call removeFile(filename,isWindowsShell,Err)
466 : !if (Err%occurred) then
467 : ! Err%msg = PROCEDURE_NAME // Err%msg
468 : ! return
469 : !end if
470 : !call removeFile(stdErr,isWindowsShell,Err)
471 : !if (Err%occurred) then
472 : ! Err%msg = PROCEDURE_NAME // Err%msg
473 : ! return
474 : !end if
475 :
476 : !call sleep(seconds=0.1_RK,Err=Err)
477 : !if (Err%occurred) then
478 : ! Err%msg = PROCEDURE_NAME // Err%msg
479 : ! return
480 : !end if
481 : !if (isWindowsShell) then ! it is Windows cmd
482 : ! command = "del " // filename // "; del " // stdErr
483 : !else
484 : ! command = "rm " // filename // "; rm " // stdErr
485 : !end if
486 : !call executeCmd( command = command//" > "//filename//" 2> "//stdErr, Err=Err )
487 : !if (Err%occurred) then
488 : ! Err%msg = PROCEDURE_NAME // &
489 : ! ": Error occurred while attempting to deleting the external file='" // filename // "'.\n" // Err%msg
490 : ! return
491 : !end if
492 :
493 27 : end subroutine getFileList
494 :
495 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
496 :
497 :
498 : end module FileList_mod ! LCOV_EXCL_LINE
|