aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--fpm/src/fpm_source_parsing.f906
-rw-r--r--fpm/src/fpm_strings.f9019
2 files changed, 21 insertions, 4 deletions
diff --git a/fpm/src/fpm_source_parsing.f90 b/fpm/src/fpm_source_parsing.f90
index f81555d..db271ed 100644
--- a/fpm/src/fpm_source_parsing.f90
+++ b/fpm/src/fpm_source_parsing.f90
@@ -16,7 +16,7 @@
!>
module fpm_source_parsing
use fpm_error, only: error_t, file_parse_error, fatal_error
-use fpm_strings, only: string_t, string_cat, split, lower, str_ends_with, fnv_1a
+use fpm_strings, only: string_t, string_cat, len_trim, split, lower, str_ends_with, fnv_1a
use fpm_model, only: srcfile_t, &
FPM_UNIT_UNKNOWN, FPM_UNIT_PROGRAM, FPM_UNIT_MODULE, &
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, &
@@ -87,7 +87,7 @@ function parse_f_source(f_filename,error) result(f_source)
close(fh)
! Ignore empty files, returned as FPM_UNIT_UNKNOW
- if (len_trim(string_cat(file_lines,' ')) < 1) return
+ if (len_trim(file_lines) < 1) return
f_source%digest = fnv_1a(file_lines)
@@ -392,7 +392,7 @@ function parse_c_source(c_filename,error) result(c_source)
close(fh)
! Ignore empty files, returned as FPM_UNIT_UNKNOW
- if (len_trim(string_cat(file_lines,' ')) < 1) then
+ if (len_trim(file_lines) < 1) then
c_source%unit_type = FPM_UNIT_UNKNOWN
return
end if
diff --git a/fpm/src/fpm_strings.f90 b/fpm/src/fpm_strings.f90
index 5b6104c..e3cee28 100644
--- a/fpm/src/fpm_strings.f90
+++ b/fpm/src/fpm_strings.f90
@@ -4,13 +4,17 @@ implicit none
private
public :: f_string, lower, split, str_ends_with, string_t
-public :: string_array_contains, string_cat, operator(.in.), fnv_1a
+public :: string_array_contains, string_cat, len_trim, operator(.in.), fnv_1a
public :: resize, str
type string_t
character(len=:), allocatable :: s
end type
+interface len_trim
+ module procedure :: string_len_trim
+end interface len_trim
+
interface resize
module procedure :: resize_string
end interface
@@ -200,6 +204,19 @@ function string_cat(strings,delim) result(cat)
end function string_cat
+
+!> Determine total trimmed length of `string_t` array
+pure function string_len_trim(strings) result(n)
+ type(string_t), intent(in) :: strings(:)
+ integer :: i, n
+
+ n = 0
+ do i=1,size(strings)
+ n = n + len_trim(strings(i)%s)
+ end do
+
+end function string_len_trim
+
subroutine split(input_line,array,delimiters,order,nulls)
! parse string on delimiter characters and store tokens into an allocatable array"
! Author: John S. Urban