Skip to content

Commit 95a0a6a

Browse files
committed
split_lines_first_last
1 parent db45771 commit 95a0a6a

File tree

2 files changed

+48
-8
lines changed

2 files changed

+48
-8
lines changed

src/fpm_filesystem.F90

Lines changed: 3 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,7 @@ module fpm_filesystem
77
OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_WINDOWS, &
88
OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD
99
use fpm_environment, only: separator, get_env, os_is_unix
10-
use fpm_strings, only: f_string, replace, string_t, split, split_first_last, dilate, str_begins_with_str
10+
use fpm_strings, only: f_string, replace, string_t, split, split_lines_first_last, dilate, str_begins_with_str
1111
use iso_c_binding, only: c_char, c_ptr, c_int, c_null_char, c_associated, c_f_pointer
1212
use fpm_error, only : fpm_stop, error_t, fatal_error
1313
implicit none
@@ -51,10 +51,6 @@ end function c_is_dir
5151
end interface
5252
#endif
5353

54-
character, parameter :: CR = achar(13)
55-
character, parameter :: LF = new_line('A')
56-
character(*), parameter :: eol = CR//LF
57-
5854
contains
5955

6056
!> Extract filename from path with/without suffix
@@ -321,7 +317,7 @@ function read_lines_expanded(filename) result(lines)
321317
return
322318
end if
323319

324-
call split_first_last(content, eol, first, last) ! TODO: \r (< macOS X), \n (>=macOS X/Linux/Unix), \r\n (Windows)
320+
call split_lines_first_last(content, first, last)
325321

326322
! allocate lines from file content string
327323
allocate (lines(size(first)))
@@ -346,7 +342,7 @@ function read_lines(filename) result(lines)
346342
return
347343
end if
348344

349-
call split_first_last(content, eol, first, last) ! TODO: \r (< macOS X), \n (>=macOS X/Linux/Unix), \r\n (Windows)
345+
call split_lines_first_last(content, first, last)
350346

351347
! allocate lines from file content string
352348
allocate (lines(size(first)))

src/fpm_strings.f90

Lines changed: 45 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -42,7 +42,7 @@ module fpm_strings
4242
implicit none
4343

4444
private
45-
public :: f_string, lower, upper, split, split_first_last, str_ends_with, string_t, str_begins_with_str
45+
public :: f_string, lower, upper, split, split_first_last, split_lines_first_last, str_ends_with, string_t, str_begins_with_str
4646
public :: to_fortran_name, is_fortran_name
4747
public :: string_array_contains, string_cat, len_trim, operator(.in.), fnv_1a
4848
public :: replace, resize, str, join, glob
@@ -551,6 +551,50 @@ pure subroutine split_first_last(string, set, first, last)
551551

552552
end subroutine split_first_last
553553

554+
!! Author: Federico Perini
555+
!! Computes the first and last indices of lines in input string, delimited
556+
!! by either CR, LF, or CRLF, and stores them into first and last output
557+
!! arrays.
558+
pure subroutine split_lines_first_last(string, first, last)
559+
character(*), intent(in) :: string
560+
integer, allocatable, intent(out) :: first(:)
561+
integer, allocatable, intent(out) :: last(:)
562+
563+
integer, dimension(len(string) + 1) :: istart, iend
564+
integer :: p, n, slen
565+
character, parameter :: CR = achar(13)
566+
character, parameter :: LF = new_line('A')
567+
568+
slen = len(string)
569+
570+
n = 0
571+
if (slen > 0) then
572+
p = 1
573+
do while (p <= slen)
574+
575+
if (index(CR//LF, string(p:p)) == 0) then
576+
n = n + 1
577+
istart(n) = p
578+
do while (p <= slen .and. index(CR//LF, string(p:p)) == 0)
579+
p = p + 1
580+
end do
581+
iend(n) = p - 1
582+
end if
583+
584+
! Handle Windows CRLF by skipping LF after CR
585+
if (p < slen) then
586+
if (string(p:p) == CR .and. string(p+1:p+1) == LF) p = p + 1
587+
endif
588+
589+
p = p + 1
590+
end do
591+
end if
592+
593+
first = istart(:n)
594+
last = iend(:n)
595+
596+
end subroutine split_lines_first_last
597+
554598
!! Author: Milan Curcic
555599
!! If back is absent, computes the leftmost token delimiter in string whose
556600
!! position is > pos. If back is present and true, computes the rightmost

0 commit comments

Comments
 (0)