Skip to content

Commit a6da02b

Browse files
committed
improve read_lines: use binary reading
1 parent c049115 commit a6da02b

File tree

2 files changed

+45
-12
lines changed

2 files changed

+45
-12
lines changed

src/fpm_filesystem.F90

Lines changed: 43 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@
22
!!
33
module fpm_filesystem
44
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, stdout=>output_unit, stderr=>error_unit
5+
use,intrinsic :: iso_c_binding, only: c_new_line
56
use fpm_environment, only: get_os_type, &
67
OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_WINDOWS, &
78
OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD
@@ -50,6 +51,8 @@ end function c_is_dir
5051
end interface
5152
#endif
5253

54+
integer, parameter :: max_line = 100000 !! maximum number of lines in a text file
55+
5356
contains
5457

5558
!> Extract filename from path with/without suffix
@@ -307,13 +310,27 @@ function read_lines_expanded(fh) result(lines)
307310
type(string_t), allocatable :: lines(:)
308311

309312
integer :: i
310-
integer :: iostat
311-
character(len=:),allocatable :: line_buffer_read
313+
integer :: length, count
314+
character(len=:), allocatable :: content
315+
integer, save :: idx(max_line) = 1
316+
317+
inquire (fh, size=length)
318+
allocate (character(len=length) :: content)
319+
320+
! read file into a single string
321+
read (fh) content
322+
count = 0
323+
do i = 1, length
324+
if (content(i:i) == c_new_line) then
325+
count = count + 1
326+
idx(count + 1) = i + 1
327+
end if
328+
end do
312329

313-
allocate(lines(number_of_rows(fh)))
314-
do i = 1, size(lines)
315-
call getline(fh, line_buffer_read, iostat)
316-
lines(i)%s = dilate(line_buffer_read)
330+
! allocate lines from file content string
331+
allocate (lines(count))
332+
do i = 1, count
333+
allocate(lines(i)%s, source=dilate(content(idx(i):idx(i + 1) - 1)))
317334
end do
318335

319336
end function read_lines_expanded
@@ -324,11 +341,27 @@ function read_lines(fh) result(lines)
324341
type(string_t), allocatable :: lines(:)
325342

326343
integer :: i
327-
integer :: iostat
344+
integer :: length, count
345+
character(len=:), allocatable :: content
346+
integer, save :: idx(max_line) = 1
347+
348+
inquire (fh, size=length)
349+
allocate (character(len=length) :: content)
350+
351+
! read file into a single string
352+
read (fh) content
353+
count = 0
354+
do i = 1, length
355+
if (content(i:i) == c_new_line) then
356+
count = count + 1
357+
idx(count + 1) = i + 1
358+
end if
359+
end do
328360

329-
allocate(lines(number_of_rows(fh)))
330-
do i = 1, size(lines)
331-
call getline(fh, lines(i)%s, iostat)
361+
! allocate lines from file content string
362+
allocate (lines(count))
363+
do i = 1, count
364+
allocate(lines(i)%s, source=content(idx(i):idx(i + 1) - 1))
332365
end do
333366

334367
end function read_lines

src/fpm_source_parsing.f90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -82,7 +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')
85+
open(newunit=fh,file=f_filename,status='old',access="stream",form="unformatted")
8686
file_lines = read_lines_expanded(fh)
8787
close(fh)
8888

@@ -427,7 +427,7 @@ function parse_c_source(c_filename,error) result(c_source)
427427
allocate(c_source%modules_provided(0))
428428
allocate(c_source%parent_modules(0))
429429

430-
open(newunit=fh,file=c_filename,status='old')
430+
open(newunit=fh,file=c_filename,status='old',access="stream",form="unformatted")
431431
file_lines = read_lines(fh)
432432
close(fh)
433433

0 commit comments

Comments
 (0)