@@ -7,7 +7,7 @@ module fpm_filesystem
7
7
OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_WINDOWS, &
8
8
OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD
9
9
use fpm_environment, only: separator, get_env, os_is_unix
10
- use fpm_strings, only: f_string, replace, string_t, split, dilate, str_begins_with_str
10
+ use fpm_strings, only: f_string, replace, string_t, split, split_first_last, dilate, str_begins_with_str
11
11
use iso_c_binding, only: c_char, c_ptr, c_int, c_null_char, c_associated, c_f_pointer
12
12
use fpm_error, only : fpm_stop, error_t, fatal_error
13
13
implicit none
@@ -51,9 +51,6 @@ end function c_is_dir
51
51
end interface
52
52
#endif
53
53
54
- integer , parameter :: max_line = 100000 ! ! maximum number of lines in a text file
55
- integer :: idx(max_line) = 1 ! ! indexes for read_lines
56
-
57
54
contains
58
55
59
56
! > Extract filename from path with/without suffix
@@ -310,27 +307,25 @@ function read_lines_expanded(fh) result(lines)
310
307
integer , intent (in ) :: fh
311
308
type (string_t), allocatable :: lines(:)
312
309
313
- integer :: i
314
- integer :: length, count
310
+ integer :: i, length
315
311
character (len= :), allocatable :: content
312
+ integer , allocatable :: first(:), last(:)
316
313
317
314
inquire (fh, size= length)
318
315
allocate (character (len= length) :: content)
316
+ if (length == 0 ) then
317
+ allocate (lines(0 ))
318
+ return
319
+ end if
319
320
320
321
! read file into a single string
321
322
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
323
+ call split_first_last(content, c_new_line, first, last) ! TODO: \r (< macOS X), \n (>=macOS X/Linux/Unix), \r\n (Windows)
329
324
330
325
! 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 )))
326
+ allocate (lines(size (first) ))
327
+ do i = 1 , size (first)
328
+ allocate (lines(i)% s, source= dilate(content(first (i):last(i) )))
334
329
end do
335
330
336
331
end function read_lines_expanded
@@ -340,27 +335,25 @@ function read_lines(fh) result(lines)
340
335
integer , intent (in ) :: fh
341
336
type (string_t), allocatable :: lines(:)
342
337
343
- integer :: i
344
- integer :: length, count
338
+ integer :: i, length
345
339
character (len= :), allocatable :: content
340
+ integer , allocatable :: first(:), last(:)
346
341
347
342
inquire (fh, size= length)
348
343
allocate (character (len= length) :: content)
344
+ if (length == 0 ) then
345
+ allocate (lines(0 ))
346
+ return
347
+ end if
349
348
350
349
! read file into a single string
351
350
read (fh) content
352
- count = 0
353
- do i = 1 , length
354
- if (content(i:i) == c_new_line) then
355
- count = count + 1
356
- idx(count + 1 ) = i + 1
357
- end if
358
- end do
351
+ call split_first_last(content, c_new_line, first, last) ! TODO: \r (< macOS X), \n (>=macOS X/Linux/Unix), \r\n (Windows)
359
352
360
353
! allocate lines from file content string
361
- allocate (lines(count ))
362
- do i = 1 , count
363
- allocate (lines(i)% s, source= content(idx (i):idx(i + 1 ) - 1 ))
354
+ allocate (lines(size (first) ))
355
+ do i = 1 , size (first)
356
+ allocate (lines(i)% s, source= content(first (i):last(i) ))
364
357
end do
365
358
366
359
end function read_lines
0 commit comments