aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--fpm/src/fpm.f902
-rw-r--r--fpm/src/fpm_sources.f9013
-rw-r--r--fpm/src/fpm_strings.f9025
3 files changed, 31 insertions, 9 deletions
diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90
index 1b32cb6..800e19e 100644
--- a/fpm/src/fpm.f90
+++ b/fpm/src/fpm.f90
@@ -1,5 +1,5 @@
module fpm
-use fpm_strings, only: string_t, str_ends_with, operator(.in.)
+use fpm_strings, only: string_t, operator(.in.)
use fpm_backend, only: build_package
use fpm_command_line, only: fpm_build_settings, fpm_new_settings, &
fpm_run_settings, fpm_install_settings, fpm_test_settings
diff --git a/fpm/src/fpm_sources.f90 b/fpm/src/fpm_sources.f90
index de2df1c..3fffa81 100644
--- a/fpm/src/fpm_sources.f90
+++ b/fpm/src/fpm_sources.f90
@@ -15,6 +15,9 @@ implicit none
private
public :: add_sources_from_dir, add_executable_sources
+character(4), parameter :: fortran_suffixes(2) = [".f90", &
+ ".f "]
+
contains
!> Wrapper to source parsing routines.
@@ -24,7 +27,7 @@ function parse_source(source_file_path,error) result(source)
type(error_t), allocatable, intent(out) :: error
type(srcfile_t) :: source
- if (str_ends_with(lower(source_file_path), ".f90")) then
+ if (str_ends_with(lower(source_file_path), fortran_suffixes)) then
source = parse_f_source(source_file_path, error)
@@ -32,8 +35,7 @@ function parse_source(source_file_path,error) result(source)
source%exe_name = basename(source_file_path,suffix=.false.)
end if
- else if (str_ends_with(lower(source_file_path), ".c") .or. &
- str_ends_with(lower(source_file_path), ".h")) then
+ else if (str_ends_with(lower(source_file_path), [".c", ".h"])) then
source = parse_c_source(source_file_path,error)
@@ -80,9 +82,8 @@ subroutine add_sources_from_dir(sources,directory,scope,with_executables,recurse
end if
is_source = [(.not.(canon_path(file_names(i)%s) .in. existing_src_files) .and. &
- (str_ends_with(lower(file_names(i)%s), ".f90") .or. &
- str_ends_with(lower(file_names(i)%s), ".c") .or. &
- str_ends_with(lower(file_names(i)%s), ".h") ),i=1,size(file_names))]
+ (str_ends_with(lower(file_names(i)%s), fortran_suffixes) .or. &
+ str_ends_with(lower(file_names(i)%s),[".c",".h"]) ),i=1,size(file_names))]
src_file_names = pack(file_names,is_source)
allocate(dir_sources(size(src_file_names)))
diff --git a/fpm/src/fpm_strings.f90 b/fpm/src/fpm_strings.f90
index 8a569cd..44a3510 100644
--- a/fpm/src/fpm_strings.f90
+++ b/fpm/src/fpm_strings.f90
@@ -19,9 +19,14 @@ interface fnv_1a
procedure :: fnv_1a_string_t
end interface fnv_1a
+interface str_ends_with
+ procedure :: str_ends_with_str
+ procedure :: str_ends_with_any
+end interface str_ends_with
+
contains
-logical function str_ends_with(s, e) result(r)
+pure logical function str_ends_with_str(s, e) result(r)
character(*), intent(in) :: s, e
integer :: n1, n2
n1 = len(s)-len(e)+1
@@ -31,7 +36,23 @@ logical function str_ends_with(s, e) result(r)
else
r = (s(n1:n2) == e)
end if
-end function str_ends_with
+end function str_ends_with_str
+
+pure logical function str_ends_with_any(s, e) result(r)
+ character(*), intent(in) :: s
+ character(*), intent(in) :: e(:)
+
+ integer :: i
+
+ r = .true.
+ do i=1,size(e)
+
+ if (str_ends_with(s,trim(e(i)))) return
+
+ end do
+ r = .false.
+
+end function str_ends_with_any
function f_string(c_string)
use iso_c_binding