Skip to content

Commit cf49f39

Browse files
authored
Add: string_len_trim to check for empty source files (#335)
Fixes performance regression from 33ad2ce. Don't use string_cat for checking for empty source files.
1 parent 6084cf0 commit cf49f39

File tree

2 files changed

+21
-4
lines changed

2 files changed

+21
-4
lines changed

fpm/src/fpm_source_parsing.f90

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -16,7 +16,7 @@
1616
!>
1717
module fpm_source_parsing
1818
use fpm_error, only: error_t, file_parse_error, fatal_error
19-
use fpm_strings, only: string_t, string_cat, split, lower, str_ends_with, fnv_1a
19+
use fpm_strings, only: string_t, string_cat, len_trim, split, lower, str_ends_with, fnv_1a
2020
use fpm_model, only: srcfile_t, &
2121
FPM_UNIT_UNKNOWN, FPM_UNIT_PROGRAM, FPM_UNIT_MODULE, &
2222
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, &
@@ -87,7 +87,7 @@ function parse_f_source(f_filename,error) result(f_source)
8787
close(fh)
8888

8989
! Ignore empty files, returned as FPM_UNIT_UNKNOW
90-
if (len_trim(string_cat(file_lines,' ')) < 1) return
90+
if (len_trim(file_lines) < 1) return
9191

9292
f_source%digest = fnv_1a(file_lines)
9393

@@ -392,7 +392,7 @@ function parse_c_source(c_filename,error) result(c_source)
392392
close(fh)
393393

394394
! Ignore empty files, returned as FPM_UNIT_UNKNOW
395-
if (len_trim(string_cat(file_lines,' ')) < 1) then
395+
if (len_trim(file_lines) < 1) then
396396
c_source%unit_type = FPM_UNIT_UNKNOWN
397397
return
398398
end if

fpm/src/fpm_strings.f90

Lines changed: 18 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -4,13 +4,17 @@ module fpm_strings
44

55
private
66
public :: f_string, lower, split, str_ends_with, string_t
7-
public :: string_array_contains, string_cat, operator(.in.), fnv_1a
7+
public :: string_array_contains, string_cat, len_trim, operator(.in.), fnv_1a
88
public :: resize, str
99

1010
type string_t
1111
character(len=:), allocatable :: s
1212
end type
1313

14+
interface len_trim
15+
module procedure :: string_len_trim
16+
end interface len_trim
17+
1418
interface resize
1519
module procedure :: resize_string
1620
end interface
@@ -200,6 +204,19 @@ function string_cat(strings,delim) result(cat)
200204

201205
end function string_cat
202206

207+
208+
!> Determine total trimmed length of `string_t` array
209+
pure function string_len_trim(strings) result(n)
210+
type(string_t), intent(in) :: strings(:)
211+
integer :: i, n
212+
213+
n = 0
214+
do i=1,size(strings)
215+
n = n + len_trim(strings(i)%s)
216+
end do
217+
218+
end function string_len_trim
219+
203220
subroutine split(input_line,array,delimiters,order,nulls)
204221
! parse string on delimiter characters and store tokens into an allocatable array"
205222
! Author: John S. Urban

0 commit comments

Comments
 (0)