Skip to content

Commit 55db69e

Browse files
authored
Merge pull request #294 from LKedward/add-f-suffix
Add: support for detecting .f and .F files
2 parents c2e043b + baea8c7 commit 55db69e

File tree

3 files changed

+31
-9
lines changed

3 files changed

+31
-9
lines changed

fpm/src/fpm.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
module fpm
2-
use fpm_strings, only: string_t, str_ends_with, operator(.in.)
2+
use fpm_strings, only: string_t, operator(.in.)
33
use fpm_backend, only: build_package
44
use fpm_command_line, only: fpm_build_settings, fpm_new_settings, &
55
fpm_run_settings, fpm_install_settings, fpm_test_settings

fpm/src/fpm_sources.f90

Lines changed: 7 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -15,6 +15,9 @@ module fpm_sources
1515
private
1616
public :: add_sources_from_dir, add_executable_sources
1717

18+
character(4), parameter :: fortran_suffixes(2) = [".f90", &
19+
".f "]
20+
1821
contains
1922

2023
!> Wrapper to source parsing routines.
@@ -24,16 +27,15 @@ function parse_source(source_file_path,error) result(source)
2427
type(error_t), allocatable, intent(out) :: error
2528
type(srcfile_t) :: source
2629

27-
if (str_ends_with(lower(source_file_path), ".f90")) then
30+
if (str_ends_with(lower(source_file_path), fortran_suffixes)) then
2831

2932
source = parse_f_source(source_file_path, error)
3033

3134
if (source%unit_type == FPM_UNIT_PROGRAM) then
3235
source%exe_name = basename(source_file_path,suffix=.false.)
3336
end if
3437

35-
else if (str_ends_with(lower(source_file_path), ".c") .or. &
36-
str_ends_with(lower(source_file_path), ".h")) then
38+
else if (str_ends_with(lower(source_file_path), [".c", ".h"])) then
3739

3840
source = parse_c_source(source_file_path,error)
3941

@@ -80,9 +82,8 @@ subroutine add_sources_from_dir(sources,directory,scope,with_executables,recurse
8082
end if
8183

8284
is_source = [(.not.(canon_path(file_names(i)%s) .in. existing_src_files) .and. &
83-
(str_ends_with(lower(file_names(i)%s), ".f90") .or. &
84-
str_ends_with(lower(file_names(i)%s), ".c") .or. &
85-
str_ends_with(lower(file_names(i)%s), ".h") ),i=1,size(file_names))]
85+
(str_ends_with(lower(file_names(i)%s), fortran_suffixes) .or. &
86+
str_ends_with(lower(file_names(i)%s),[".c",".h"]) ),i=1,size(file_names))]
8687
src_file_names = pack(file_names,is_source)
8788

8889
allocate(dir_sources(size(src_file_names)))

fpm/src/fpm_strings.f90

Lines changed: 23 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -19,9 +19,14 @@ module fpm_strings
1919
procedure :: fnv_1a_string_t
2020
end interface fnv_1a
2121

22+
interface str_ends_with
23+
procedure :: str_ends_with_str
24+
procedure :: str_ends_with_any
25+
end interface str_ends_with
26+
2227
contains
2328

24-
logical function str_ends_with(s, e) result(r)
29+
pure logical function str_ends_with_str(s, e) result(r)
2530
character(*), intent(in) :: s, e
2631
integer :: n1, n2
2732
n1 = len(s)-len(e)+1
@@ -31,7 +36,23 @@ logical function str_ends_with(s, e) result(r)
3136
else
3237
r = (s(n1:n2) == e)
3338
end if
34-
end function str_ends_with
39+
end function str_ends_with_str
40+
41+
pure logical function str_ends_with_any(s, e) result(r)
42+
character(*), intent(in) :: s
43+
character(*), intent(in) :: e(:)
44+
45+
integer :: i
46+
47+
r = .true.
48+
do i=1,size(e)
49+
50+
if (str_ends_with(s,trim(e(i)))) return
51+
52+
end do
53+
r = .false.
54+
55+
end function str_ends_with_any
3556

3657
function f_string(c_string)
3758
use iso_c_binding

0 commit comments

Comments
 (0)