@@ -51,6 +51,8 @@ end function c_is_dir
51
51
end interface
52
52
#endif
53
53
54
+ character (* ), parameter :: eol = new_line(' a' ) ! ! End of line
55
+
54
56
contains
55
57
56
58
! > Extract filename from path with/without suffix
@@ -303,24 +305,21 @@ integer function number_of_rows(s) result(nrows)
303
305
end function number_of_rows
304
306
305
307
! > read lines into an array of TYPE(STRING_T) variables expanding tabs
306
- function read_lines_expanded (fh ) result(lines)
307
- integer , intent (in ) :: fh
308
+ function read_lines_expanded (filename ) result(lines)
309
+ character (len =* ) , intent (in ) :: filename
308
310
type (string_t), allocatable :: lines(:)
309
311
310
- integer :: i, length
312
+ integer :: i
311
313
character (len= :), allocatable :: content
312
314
integer , allocatable :: first(:), last(:)
313
315
314
- inquire (fh, size= length)
315
- allocate (character (len= length) :: content)
316
- if (length == 0 ) then
316
+ content = read_text_file(filename)
317
+ if (len (content) == 0 ) then
317
318
allocate (lines(0 ))
318
319
return
319
320
end if
320
321
321
- ! read file into a single string
322
- read (fh) content
323
- call split_first_last(content, c_new_line, first, last) ! TODO: \r (< macOS X), \n (>=macOS X/Linux/Unix), \r\n (Windows)
322
+ call split_first_last(content, eol, first, last) ! TODO: \r (< macOS X), \n (>=macOS X/Linux/Unix), \r\n (Windows)
324
323
325
324
! allocate lines from file content string
326
325
allocate (lines(size (first)))
@@ -331,24 +330,21 @@ function read_lines_expanded(fh) result(lines)
331
330
end function read_lines_expanded
332
331
333
332
! > read lines into an array of TYPE(STRING_T) variables
334
- function read_lines (fh ) result(lines)
335
- integer , intent (in ) :: fh
333
+ function read_lines (filename ) result(lines)
334
+ character (len =* ) , intent (in ) :: filename
336
335
type (string_t), allocatable :: lines(:)
337
336
338
- integer :: i, length
337
+ integer :: i
339
338
character (len= :), allocatable :: content
340
339
integer , allocatable :: first(:), last(:)
341
340
342
- inquire (fh, size= length)
343
- allocate (character (len= length) :: content)
344
- if (length == 0 ) then
341
+ content = read_text_file(filename)
342
+ if (len (content) == 0 ) then
345
343
allocate (lines(0 ))
346
344
return
347
345
end if
348
346
349
- ! read file into a single string
350
- read (fh) content
351
- call split_first_last(content, c_new_line, first, last) ! TODO: \r (< macOS X), \n (>=macOS X/Linux/Unix), \r\n (Windows)
347
+ call split_first_last(content, eol, first, last) ! TODO: \r (< macOS X), \n (>=macOS X/Linux/Unix), \r\n (Windows)
352
348
353
349
! allocate lines from file content string
354
350
allocate (lines(size (first)))
@@ -358,6 +354,22 @@ function read_lines(fh) result(lines)
358
354
359
355
end function read_lines
360
356
357
+ ! > read text file into a string
358
+ function read_text_file (filename ) result(string)
359
+ character (len=* ), intent (in ) :: filename
360
+ character (len= :), allocatable :: string
361
+ integer :: fh, length
362
+
363
+ open (newunit= fh, file= filename, status= ' old' , action= ' read' , &
364
+ access= ' stream' , form= ' unformatted' )
365
+ inquire (fh, size= length)
366
+ allocate (character (len= length) :: string)
367
+ if (length == 0 ) return
368
+ read (fh) string
369
+ close (fh)
370
+
371
+ end function read_text_file
372
+
361
373
! > Create a directory. Create subdirectories as needed
362
374
subroutine mkdir (dir , echo )
363
375
character (len=* ), intent (in ) :: dir
@@ -505,9 +517,8 @@ recursive subroutine list_files(dir, files, recurse)
505
517
call fpm_stop(2 ,' *list_files*:directory listing failed' )
506
518
end if
507
519
508
- open (newunit= fh, file= temp_file, status= ' old' ,access= ' stream' ,form= ' unformatted' )
509
- files = read_lines(fh)
510
- close (fh,status= " delete" )
520
+ files = read_lines(temp_file)
521
+ call delete_file(temp_file)
511
522
512
523
do i= 1 ,size (files)
513
524
files(i)% s = join_path(dir,files(i)% s)
0 commit comments