Skip to content

Commit 36e82f2

Browse files
committed
Add support for toggling Fortran features
1 parent 55d94b0 commit 36e82f2

File tree

19 files changed

+308
-8
lines changed

19 files changed

+308
-8
lines changed

ci/run_tests.sh

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -158,6 +158,14 @@ pushd cpp_files
158158
"$fpm" test
159159
popd
160160

161+
# Test Fortran features
162+
for feature in free-format fixed-format implicit-typing implicit-external
163+
do
164+
pushd $feature
165+
"$fpm" run
166+
popd
167+
done
168+
161169
# Test app exit codes
162170
pushd fpm_test_exit_code
163171
"$fpm" build
Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,4 @@
1+
program test
2+
use lib
3+
call hello
4+
end
Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,2 @@
1+
name = "fixed-format"
2+
fortran.source-format = "fixed"
Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,7 @@
1+
module lib
2+
contains
3+
subroutine h e l l o
4+
print '(a)',
5+
+"Hello, fixed world!"
6+
end subroutine
7+
end module
Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,4 @@
1+
program test
2+
use lib
3+
call hello
4+
end

example_packages/free-format/fpm.toml

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
name = "free-format"
2+
fortran.source-format = "free"
3+
executable = [{main="main.f", name="free-format"}]
Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,6 @@
1+
module lib
2+
contains
3+
subroutine hello
4+
print '(a)', "Hello, free world!"
5+
end subroutine
6+
end module
Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,5 @@
1+
program test
2+
integer :: ijk
3+
call impl(ijk)
4+
if (ijk /= 1) error stop
5+
end program test
Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,2 @@
1+
name = "implicit-external"
2+
fortran.implicit-external = true
Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,4 @@
1+
subroutine impl(ijk)
2+
integer :: ijk
3+
ijk = 1
4+
end subroutine impl
Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,4 @@
1+
program test
2+
use impl
3+
if (ijk /= 1) error stop
4+
end program
Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,2 @@
1+
name = "implicit-typing"
2+
fortran.implicit-typing = true
Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
module impl
2+
parameter(ijk = 1)
3+
end module

src/fpm.f90

Lines changed: 6 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,7 @@ module fpm
1010
use fpm_environment, only: get_env
1111
use fpm_filesystem, only: is_dir, join_path, list_files, exists, &
1212
basename, filewrite, mkdir, run, os_delete_dir
13-
use fpm_model, only: fpm_model_t, srcfile_t, show_model, &
13+
use fpm_model, only: fpm_model_t, srcfile_t, show_model, fortran_features_t, &
1414
FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, FPM_SCOPE_DEP, &
1515
FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST
1616
use fpm_compiler, only: new_compiler, new_archiver, set_cpp_preprocessor_flags
@@ -112,6 +112,11 @@ subroutine build_model(model, settings, package, error)
112112
if (allocated(error)) exit
113113

114114
model%packages(i)%name = dependency%name
115+
associate(features => model%packages(i)%features)
116+
features%implicit_typing = dependency%fortran%implicit_typing
117+
features%implicit_external = dependency%fortran%implicit_external
118+
features%source_format = dependency%fortran%source_format
119+
end associate
115120
call package%version%to_string(version)
116121
model%packages(i)%version = version
117122

src/fpm/manifest/fortran.f90

Lines changed: 105 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,105 @@
1+
module fpm_manifest_fortran
2+
use fpm_error, only : error_t, syntax_error, fatal_error
3+
use fpm_toml, only : toml_table, toml_key, toml_stat, get_value
4+
implicit none
5+
private
6+
7+
public :: fortran_config_t, new_fortran_config
8+
9+
!> Configuration data for Fortran
10+
type :: fortran_config_t
11+
12+
!> Enable default implicit typing
13+
logical :: implicit_typing
14+
15+
!> Enable implicit external interfaces
16+
logical :: implicit_external
17+
18+
!> Use free format for all Fortran sources
19+
character(:), allocatable :: source_format
20+
21+
end type fortran_config_t
22+
23+
contains
24+
25+
!> Construct a new build configuration from a TOML data structure
26+
subroutine new_fortran_config(self, table, error)
27+
28+
!> Instance of the fortran configuration
29+
type(fortran_config_t), intent(out) :: self
30+
31+
!> Instance of the TOML data structure
32+
type(toml_table), intent(inout) :: table
33+
34+
!> Error handling
35+
type(error_t), allocatable, intent(out) :: error
36+
37+
integer :: stat
38+
character(:), allocatable :: source_format
39+
40+
call check(table, error)
41+
if (allocated(error)) return
42+
43+
call get_value(table, "implicit-typing", self%implicit_typing, .false., stat=stat)
44+
45+
if (stat /= toml_stat%success) then
46+
call fatal_error(error,"Error while reading value for 'implicit-typing' in fpm.toml, expecting logical")
47+
return
48+
end if
49+
50+
call get_value(table, "implicit-external", self%implicit_external, .false., stat=stat)
51+
52+
if (stat /= toml_stat%success) then
53+
call fatal_error(error,"Error while reading value for 'implicit-external' in fpm.toml, expecting logical")
54+
return
55+
end if
56+
57+
call get_value(table, "source-format", source_format, "free", stat=stat)
58+
59+
if (stat /= toml_stat%success) then
60+
call fatal_error(error,"Error while reading value for 'source-format' in fpm.toml, expecting logical")
61+
return
62+
end if
63+
select case(source_format)
64+
case default
65+
call fatal_error(error,"Value of source-format cannot be '"//source_format//"'")
66+
return
67+
case("free", "fixed", "default")
68+
self%source_format = source_format
69+
end select
70+
71+
end subroutine new_fortran_config
72+
73+
!> Check local schema for allowed entries
74+
subroutine check(table, error)
75+
76+
!> Instance of the TOML data structure
77+
type(toml_table), intent(inout) :: table
78+
79+
!> Error handling
80+
type(error_t), allocatable, intent(out) :: error
81+
82+
type(toml_key), allocatable :: list(:)
83+
integer :: ikey
84+
85+
call table%get_keys(list)
86+
87+
! table can be empty
88+
if (size(list) < 1) return
89+
90+
do ikey = 1, size(list)
91+
select case(list(ikey)%key)
92+
93+
case("implicit-typing", "implicit-external", "source-format")
94+
continue
95+
96+
case default
97+
call syntax_error(error, "Key "//list(ikey)%key//" is not allowed in fortran")
98+
exit
99+
100+
end select
101+
end do
102+
103+
end subroutine check
104+
105+
end module fpm_manifest_fortran

src/fpm/manifest/package.f90

Lines changed: 14 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -27,6 +27,7 @@
2727
!>[profiles]
2828
!>[build]
2929
!>[install]
30+
!>[fortran]
3031
!>[[ executable ]]
3132
!>[[ example ]]
3233
!>[[ test ]]
@@ -38,6 +39,7 @@ module fpm_manifest_package
3839
use fpm_manifest_profile, only : profile_config_t, new_profiles, get_default_profiles
3940
use fpm_manifest_example, only : example_config_t, new_example
4041
use fpm_manifest_executable, only : executable_config_t, new_executable
42+
use fpm_manifest_fortran, only : fortran_config_t, new_fortran_config
4143
use fpm_manifest_library, only : library_config_t, new_library
4244
use fpm_manifest_install, only: install_config_t, new_install_config
4345
use fpm_manifest_test, only : test_config_t, new_test
@@ -75,6 +77,9 @@ module fpm_manifest_package
7577
!> Installation configuration data
7678
type(install_config_t) :: install
7779

80+
!> Fortran meta data
81+
type(fortran_config_t) :: fortran
82+
7883
!> Library meta data
7984
type(library_config_t), allocatable :: library
8085

@@ -173,6 +178,14 @@ subroutine new_package(self, table, root, error)
173178
call new_install_config(self%install, child, error)
174179
if (allocated(error)) return
175180

181+
call get_value(table, "fortran", child, requested=.true., stat=stat)
182+
if (stat /= toml_stat%success) then
183+
call fatal_error(error, "Type mismatch for fortran entry, must be a table")
184+
return
185+
end if
186+
call new_fortran_config(self%fortran, child, error)
187+
if (allocated(error)) return
188+
176189
call get_value(table, "version", version, "0")
177190
call new_version(self%version, version, error)
178191
if (allocated(error) .and. present(root)) then
@@ -328,7 +341,7 @@ subroutine check(table, error)
328341
case("version", "license", "author", "maintainer", "copyright", &
329342
& "description", "keywords", "categories", "homepage", "build", &
330343
& "dependencies", "dev-dependencies", "profiles", "test", "executable", &
331-
& "example", "library", "install", "extra", "preprocess")
344+
& "example", "library", "install", "extra", "preprocess", "fortran")
332345
continue
333346

334347
end select

src/fpm_compiler.F90

Lines changed: 73 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -94,6 +94,8 @@ module fpm_compiler
9494
procedure :: get_module_flag
9595
!> Get flag for include directories
9696
procedure :: get_include_flag
97+
!> Get feature flag
98+
procedure :: get_feature_flag
9799
!> Compile a Fortran object
98100
procedure :: compile_fortran
99101
!> Compile a C object
@@ -137,10 +139,14 @@ module fpm_compiler
137139
flag_gnu_opt = " -O3 -funroll-loops", &
138140
flag_gnu_debug = " -g", &
139141
flag_gnu_pic = " -fPIC", &
140-
flag_gnu_warn = " -Wall -Wextra -Wimplicit-interface", &
142+
flag_gnu_warn = " -Wall -Wextra", &
141143
flag_gnu_check = " -fcheck=bounds -fcheck=array-temps", &
142144
flag_gnu_limit = " -fmax-errors=1", &
143-
flag_gnu_external = " -Wimplicit-interface"
145+
flag_gnu_external = " -Wimplicit-interface", &
146+
flag_gnu_no_implicit_typing = " -fimplicit-none", &
147+
flag_gnu_no_implicit_external = " -Werror=implicit-interface", &
148+
flag_gnu_free_format = " -ffree-form", &
149+
flag_gnu_fixed_format = " -ffixed-form"
144150

145151
character(*), parameter :: &
146152
flag_pgi_backslash = " -Mbackslash", &
@@ -185,7 +191,10 @@ module fpm_compiler
185191
flag_nag_backtrace = " -gline"
186192

187193
character(*), parameter :: &
188-
flag_lfortran_opt = " --fast"
194+
flag_lfortran_opt = " --fast", &
195+
flag_lfortran_implicit_typing = " --implicit-typing", &
196+
flag_lfortran_implicit_external = " --allow-implicit-interface", &
197+
flag_lfortran_fixed_format = " --fixed-form"
189198

190199

191200
contains
@@ -539,6 +548,67 @@ function get_module_flag(self, path) result(flags)
539548
end function get_module_flag
540549

541550

551+
function get_feature_flag(self, feature) result(flags)
552+
class(compiler_t), intent(in) :: self
553+
character(len=*), intent(in) :: feature
554+
character(len=:), allocatable :: flags
555+
556+
flags = ""
557+
select case(feature)
558+
case("no-implicit-typing")
559+
select case(self%id)
560+
case(id_caf, id_gcc, id_f95)
561+
flags = flag_gnu_no_implicit_typing
562+
563+
end select
564+
565+
case("implicit-typing")
566+
select case(self%id)
567+
case(id_lfortran)
568+
flags = flag_lfortran_implicit_typing
569+
570+
end select
571+
572+
case("no-implicit-external")
573+
select case(self%id)
574+
case(id_caf, id_gcc, id_f95)
575+
flags = flag_gnu_no_implicit_external
576+
577+
end select
578+
579+
case("implicit-external")
580+
select case(self%id)
581+
case(id_lfortran)
582+
flags = flag_lfortran_implicit_external
583+
584+
end select
585+
586+
case("free-format")
587+
select case(self%id)
588+
case(id_caf, id_gcc, id_f95)
589+
flags = flag_gnu_free_format
590+
591+
end select
592+
593+
case("fixed-format")
594+
select case(self%id)
595+
case(id_caf, id_gcc, id_f95)
596+
flags = flag_gnu_fixed_format
597+
598+
case(id_lfortran)
599+
flags = flag_lfortran_fixed_format
600+
601+
end select
602+
603+
case("default-format")
604+
continue
605+
606+
case default
607+
error stop "Unknown feature '"//feature//"'"
608+
end select
609+
end function get_feature_flag
610+
611+
542612
subroutine get_default_c_compiler(f_compiler, c_compiler)
543613
character(len=*), intent(in) :: f_compiler
544614
character(len=:), allocatable, intent(out) :: c_compiler

0 commit comments

Comments
 (0)