diff --git a/src/fpm.f90 b/src/fpm.f90 index 561fb4e5e9..2d04aefd04 100644 --- a/src/fpm.f90 +++ b/src/fpm.f90 @@ -108,6 +108,7 @@ subroutine build_model(model, settings, package, error) features%implicit_typing = dependency%fortran%implicit_typing features%implicit_external = dependency%fortran%implicit_external features%source_form = dependency%fortran%source_form + features%user_defined_flags = dependency%fortran%user_defined_flags end associate model%packages(i)%version = package%version%s() diff --git a/src/fpm/manifest/fortran.f90 b/src/fpm/manifest/fortran.f90 index 083d61fe1e..40080379cb 100644 --- a/src/fpm/manifest/fortran.f90 +++ b/src/fpm/manifest/fortran.f90 @@ -16,7 +16,7 @@ module fpm_manifest_fortran logical :: implicit_external = .false. !> Form to use for all Fortran sources - character(:), allocatable :: source_form + character(:), allocatable :: source_form, user_defined_flags contains @@ -44,7 +44,7 @@ subroutine new_fortran_config(self, table, error) type(error_t), allocatable, intent(out) :: error integer :: stat - character(:), allocatable :: source_form + character(:), allocatable :: source_form, user_defined_flags call check(table, error) if (allocated(error)) return @@ -77,6 +77,14 @@ subroutine new_fortran_config(self, table, error) self%source_form = source_form end select + call get_value(table, "user-defined-flags", user_defined_flags, "", stat=stat) + if (stat /= toml_stat%success) then + call fatal_error(error,"Error while reading value for 'user-defined-flags' in fpm.toml") + return + end if + + self%user_defined_flags = user_defined_flags + end subroutine new_fortran_config !> Check local schema for allowed entries @@ -99,7 +107,7 @@ subroutine check(table, error) do ikey = 1, size(list) select case(list(ikey)%key) - case("implicit-typing", "implicit-external", "source-form") + case("implicit-typing", "implicit-external", "source-form", "user-defined-flags") continue case default @@ -123,6 +131,8 @@ logical function fortran_is_same(this,that) if (this%implicit_external.neqv.other%implicit_external) return if (.not.allocated(this%source_form).eqv.allocated(other%source_form)) return if (.not.this%source_form==other%source_form) return + if (.not.allocated(this%user_defined_flags).eqv.allocated(other%user_defined_flags)) return + if (.not.this%user_defined_flags==other%user_defined_flags) return class default ! Not the same type return @@ -151,6 +161,8 @@ subroutine dump_to_toml(self, table, error) if (allocated(error)) return call set_string(table, "source-form", self%source_form, error, class_name) if (allocated(error)) return + call set_string(table, "user-defined-flags", self%user_defined_flags, error, class_name) + if (allocated(error)) return end subroutine dump_to_toml @@ -171,6 +183,7 @@ subroutine load_from_toml(self, table, error) call get_value(table, "implicit-external", self%implicit_external, error, class_name) if (allocated(error)) return call get_value(table, "source-form", self%source_form) + call get_value(table, "user-defined-flags", self%user_defined_flags) end subroutine load_from_toml diff --git a/src/fpm_model.f90 b/src/fpm_model.f90 index 2db459f26f..9629f6cb84 100644 --- a/src/fpm_model.f90 +++ b/src/fpm_model.f90 @@ -93,7 +93,7 @@ module fpm_model logical :: implicit_external = .false. !> Form to use for all Fortran sources - character(:), allocatable :: source_form + character(:), allocatable :: source_form, user_defined_flags contains @@ -599,6 +599,7 @@ logical function fft_is_same(this,that) if (.not.(this%implicit_typing.eqv.other%implicit_typing)) return if (.not.(this%implicit_external.eqv.other%implicit_external)) return if (.not.(this%source_form==other%source_form)) return + if (.not.(this%user_defined_flags==other%user_defined_flags)) return class default ! Not the same type @@ -628,6 +629,8 @@ subroutine fft_dump_to_toml(self, table, error) if (allocated(error)) return call set_string(table, "source-form", self%source_form, error, 'fortran_features_t') if (allocated(error)) return + call set_string(table, "user-defined-flags", self%user_defined_flags, error, 'fortran_features_t') + if (allocated(error)) return end subroutine fft_dump_to_toml @@ -651,6 +654,7 @@ subroutine fft_load_from_toml(self, table, error) if (allocated(error)) return ! Return unallocated value if not present call get_value(table, "source-form", self%source_form) + call get_value(table, "user-defined-flags", self%user_defined_flags) end subroutine fft_load_from_toml diff --git a/src/fpm_targets.f90 b/src/fpm_targets.f90 index 38a7718aac..7c6624a3be 100644 --- a/src/fpm_targets.f90 +++ b/src/fpm_targets.f90 @@ -1103,6 +1103,10 @@ function get_feature_flags(compiler, features) result(flags) if (allocated(features%source_form)) then flags = flags // compiler%get_feature_flag(features%source_form//"-form") end if + + if (allocated(features%user_defined_flags)) then + flags = flags // " " // features%user_defined_flags + end if end function get_feature_flags end module fpm_targets diff --git a/test/fpm_test/test_toml.f90 b/test/fpm_test/test_toml.f90 index ad0a8b40c9..c58e6b83b8 100644 --- a/test/fpm_test/test_toml.f90 +++ b/test/fpm_test/test_toml.f90 @@ -610,6 +610,10 @@ subroutine fft_roundtrip(error) call fortran%test_serialization('fortran_features_t: with form',error) if (allocated(error)) return + fortran%user_defined_flags = "--ffree-line-length-none" + call fortran%test_serialization('fortran_features_t: with user-defined-flags',error) + if (allocated(error)) return + end subroutine fft_roundtrip !> Test deserialization of an invalid fortran-features structure @@ -623,7 +627,8 @@ subroutine fft_invalid(error) character(len=*), parameter :: toml = 'implicit-typing = false '//NL//& & 'implicit-external = 0 '//NL//& ! not a boolean - & 'source-form = "free" ' + & 'source-form = "free" '//NL//& + & 'user-defined-flags = "--ffree-line-length-none" ' call string_to_toml(toml, table) @@ -651,6 +656,7 @@ subroutine package_roundtrip(error) pkg%enforce_module_names = .false. pkg%module_prefix = string_t("") pkg%features%source_form = "free" + pkg%features%user_defined_flags = "--ffree-line-length-none" if (allocated(pkg%sources)) deallocate(pkg%sources) allocate(pkg%sources(4)) @@ -931,6 +937,7 @@ subroutine fpm_081_table(table) fpm = fpm//NL//'implicit-typing = false' fpm = fpm//NL//'implicit-external = false' fpm = fpm//NL//'source-form = "free"' + fpm = fpm//NL//'user-defined-flags = "--ffree-line-length-none"' fpm = fpm//NL//'[packages.fpm.sources]' fpm = fpm//NL//'[packages.fpm.sources.src_1]' fpm = fpm//NL//'file-name = "././src/fpm.f90"' @@ -1002,6 +1009,7 @@ subroutine fpm_081_table(table) fpm = fpm//NL//'implicit-typing = false' fpm = fpm//NL//'implicit-external = false' fpm = fpm//NL//'source-form = "free"' + fpm = fpm//NL//'user-defined-flags = "--ffree-line-length-none"' fpm = fpm//NL//'[packages.toml-f.sources]' fpm = fpm//NL//'[packages.toml-f.sources.src_1]' fpm = fpm//NL//'file-name = "build/dependencies/toml-f/src/tomlf.f90"' @@ -1032,6 +1040,7 @@ subroutine fpm_081_table(table) fpm = fpm//NL//'implicit-typing = false' fpm = fpm//NL//'implicit-external = false' fpm = fpm//NL//'source-form = "free"' + fpm = fpm//NL//'flags = "--ffree-line-length-none"' fpm = fpm//NL//'[packages.M_CLI2.sources]' fpm = fpm//NL//'[packages.M_CLI2.sources.src_1]' fpm = fpm//NL//'file-name = "build/dependencies/M_CLI2/src/M_CLI2.F90"' @@ -1052,6 +1061,7 @@ subroutine fpm_081_table(table) fpm = fpm//NL//'implicit-typing = false' fpm = fpm//NL//'implicit-external = false' fpm = fpm//NL//'source-form = "free"' + fpm = fpm//NL//'user-defined-flags = "--ffree-line-length-none"' fpm = fpm//NL//'[packages.jonquil.sources]' fpm = fpm//NL//'[packages.jonquil.sources.src_1]' fpm = fpm//NL//'file-name = "build/dependencies/jonquil/src/jonquil.f90"' @@ -1186,6 +1196,7 @@ subroutine fortran_features_roundtrip(error) fortran%implicit_external = .true. fortran%implicit_typing = .false. fortran%source_form = 'free' + fortran%user_defined_flags = '--ffree-line-length-none' call fortran%test_serialization('fortran_features_roundtrip',error) if (allocated(error)) return @@ -1193,6 +1204,9 @@ subroutine fortran_features_roundtrip(error) deallocate(fortran%source_form) call fortran%test_serialization('fortran_features_roundtrip 2',error) + deallocate(fortran%user_defined_flags) + call fortran%test_serialization('fortran_features_roundtrip 3',error) + end subroutine fortran_features_roundtrip subroutine library_config_roundtrip(error)