Skip to content

Commit 067cc3c

Browse files
committed
add read_text_file
1 parent a16f4b5 commit 067cc3c

File tree

2 files changed

+34
-27
lines changed

2 files changed

+34
-27
lines changed

src/fpm_filesystem.F90

Lines changed: 32 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -51,6 +51,8 @@ end function c_is_dir
5151
end interface
5252
#endif
5353

54+
character(*), parameter :: eol = new_line('a') !! End of line
55+
5456
contains
5557

5658
!> Extract filename from path with/without suffix
@@ -303,24 +305,21 @@ integer function number_of_rows(s) result(nrows)
303305
end function number_of_rows
304306

305307
!> 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
308310
type(string_t), allocatable :: lines(:)
309311

310-
integer :: i, length
312+
integer :: i
311313
character(len=:), allocatable :: content
312314
integer, allocatable :: first(:), last(:)
313315

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
317318
allocate (lines(0))
318319
return
319320
end if
320321

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)
324323

325324
! allocate lines from file content string
326325
allocate (lines(size(first)))
@@ -331,24 +330,21 @@ function read_lines_expanded(fh) result(lines)
331330
end function read_lines_expanded
332331

333332
!> 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
336335
type(string_t), allocatable :: lines(:)
337336

338-
integer :: i, length
337+
integer :: i
339338
character(len=:), allocatable :: content
340339
integer, allocatable :: first(:), last(:)
341340

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
345343
allocate (lines(0))
346344
return
347345
end if
348346

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)
352348

353349
! allocate lines from file content string
354350
allocate (lines(size(first)))
@@ -358,6 +354,22 @@ function read_lines(fh) result(lines)
358354

359355
end function read_lines
360356

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+
361373
!> Create a directory. Create subdirectories as needed
362374
subroutine mkdir(dir, echo)
363375
character(len=*), intent(in) :: dir
@@ -505,9 +517,8 @@ recursive subroutine list_files(dir, files, recurse)
505517
call fpm_stop(2,'*list_files*:directory listing failed')
506518
end if
507519

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)
511522

512523
do i=1,size(files)
513524
files(i)%s = join_path(dir,files(i)%s)

src/fpm_source_parsing.f90

Lines changed: 2 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -82,9 +82,7 @@ function parse_f_source(f_filename,error) result(f_source)
8282

8383
f_source%file_name = f_filename
8484

85-
open(newunit=fh,file=f_filename,status='old',access='stream',form='unformatted')
86-
file_lines = read_lines_expanded(fh)
87-
close(fh)
85+
file_lines = read_lines_expanded(f_filename)
8886

8987
! for efficiency in parsing make a lowercase left-adjusted copy of the file
9088
! Need a copy because INCLUDE (and #include) file arguments are case-sensitive
@@ -427,9 +425,7 @@ function parse_c_source(c_filename,error) result(c_source)
427425
allocate(c_source%modules_provided(0))
428426
allocate(c_source%parent_modules(0))
429427

430-
open(newunit=fh,file=c_filename,status='old',access='stream',form='unformatted')
431-
file_lines = read_lines(fh)
432-
close(fh)
428+
file_lines = read_lines(c_filename)
433429

434430
! Ignore empty files, returned as FPM_UNIT_UNKNOWN
435431
if (len_trim(file_lines) < 1) then

0 commit comments

Comments
 (0)