Skip to content

Commit befef9a

Browse files
authored
remove duplicate class fortran_features_t, replace with fortran_config_t (#1175)
2 parents c558772 + da19947 commit befef9a

File tree

5 files changed

+15
-106
lines changed

5 files changed

+15
-106
lines changed

src/fpm.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,7 @@ module fpm
99
use fpm_dependency, only : new_dependency_tree
1010
use fpm_filesystem, only: is_dir, join_path, list_files, exists, &
1111
basename, filewrite, mkdir, run, os_delete_dir
12-
use fpm_model, only: fpm_model_t, srcfile_t, show_model, fortran_features_t, &
12+
use fpm_model, only: fpm_model_t, srcfile_t, show_model, &
1313
FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, FPM_SCOPE_DEP, &
1414
FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST
1515
use fpm_compiler, only: new_compiler, new_archiver, set_cpp_preprocessor_flags

src/fpm_model.f90

Lines changed: 3 additions & 94 deletions
Original file line numberDiff line numberDiff line change
@@ -46,10 +46,11 @@ module fpm_model
4646
use fpm_error, only: error_t, fatal_error
4747
use fpm_environment, only: OS_WINDOWS,OS_MACOS
4848
use fpm_manifest_preprocess, only: preprocess_config_t
49+
use fpm_manifest_fortran, only: fortran_config_t
4950
implicit none
5051

5152
private
52-
public :: fpm_model_t, srcfile_t, show_model, fortran_features_t, package_t
53+
public :: fpm_model_t, srcfile_t, show_model, fortran_config_t, package_t
5354

5455
public :: FPM_UNIT_UNKNOWN, FPM_UNIT_PROGRAM, FPM_UNIT_MODULE, &
5556
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, FPM_UNIT_CSOURCE, &
@@ -86,27 +87,6 @@ module fpm_model
8687
integer, parameter :: FPM_SCOPE_TEST = 4
8788
integer, parameter :: FPM_SCOPE_EXAMPLE = 5
8889

89-
!> Enabled Fortran language features
90-
type, extends(serializable_t) :: fortran_features_t
91-
92-
!> Use default implicit typing
93-
logical :: implicit_typing = .false.
94-
95-
!> Use implicit external interface
96-
logical :: implicit_external = .false.
97-
98-
!> Form to use for all Fortran sources
99-
character(:), allocatable :: source_form
100-
101-
contains
102-
103-
!> Serialization interface
104-
procedure :: serializable_is_same => fft_is_same
105-
procedure :: dump_to_toml => fft_dump_to_toml
106-
procedure :: load_from_toml => fft_load_from_toml
107-
108-
end type fortran_features_t
109-
11090
!> Type for describing a source file
11191
type, extends(serializable_t) :: srcfile_t
11292
!> File path relative to cwd
@@ -171,7 +151,7 @@ module fpm_model
171151
type(string_t) :: module_prefix
172152

173153
!> Language features
174-
type(fortran_features_t) :: features
154+
type(fortran_config_t) :: features
175155

176156
contains
177157

@@ -614,77 +594,6 @@ subroutine srcfile_load_from_toml(self, table, error)
614594

615595
end subroutine srcfile_load_from_toml
616596

617-
!> Check that two fortran feature objects are equal
618-
logical function fft_is_same(this,that)
619-
class(fortran_features_t), intent(in) :: this
620-
class(serializable_t), intent(in) :: that
621-
622-
fft_is_same = .false.
623-
624-
select type (other=>that)
625-
type is (fortran_features_t)
626-
627-
if (.not.(this%implicit_typing.eqv.other%implicit_typing)) return
628-
if (.not.(this%implicit_external.eqv.other%implicit_external)) return
629-
if (allocated(this%source_form).neqv.allocated(other%source_form)) return
630-
if (allocated(this%source_form)) then
631-
if (.not.(this%source_form==other%source_form)) return
632-
end if
633-
634-
class default
635-
! Not the same type
636-
return
637-
end select
638-
639-
!> All checks passed!
640-
fft_is_same = .true.
641-
642-
end function fft_is_same
643-
644-
!> Dump fortran features to toml table
645-
subroutine fft_dump_to_toml(self, table, error)
646-
647-
!> Instance of the serializable object
648-
class(fortran_features_t), intent(inout) :: self
649-
650-
!> Data structure
651-
type(toml_table), intent(inout) :: table
652-
653-
!> Error handling
654-
type(error_t), allocatable, intent(out) :: error
655-
656-
call set_value(table, "implicit-typing", self%implicit_typing, error, 'fortran_features_t')
657-
if (allocated(error)) return
658-
call set_value(table, "implicit-external", self%implicit_external, error, 'fortran_features_t')
659-
if (allocated(error)) return
660-
call set_string(table, "source-form", self%source_form, error, 'fortran_features_t')
661-
if (allocated(error)) return
662-
663-
end subroutine fft_dump_to_toml
664-
665-
!> Read dependency from toml table (no checks made at this stage)
666-
subroutine fft_load_from_toml(self, table, error)
667-
668-
!> Instance of the serializable object
669-
class(fortran_features_t), intent(inout) :: self
670-
671-
!> Data structure
672-
type(toml_table), intent(inout) :: table
673-
674-
!> Error handling
675-
type(error_t), allocatable, intent(out) :: error
676-
677-
integer :: ierr
678-
679-
call get_value(table, "implicit-typing", self%implicit_typing, error, 'fortran_features_t')
680-
if (allocated(error)) return
681-
call get_value(table, "implicit-external", self%implicit_external, error, 'fortran_features_t')
682-
if (allocated(error)) return
683-
! Return unallocated value if not present
684-
call get_value(table, "source-form", self%source_form)
685-
686-
end subroutine fft_load_from_toml
687-
688597
!> Check that two package objects are equal
689598
logical function package_is_same(this,that)
690599
class(package_t), intent(in) :: this

src/fpm_targets.f90

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -123,7 +123,7 @@ module fpm_targets
123123
logical :: skip = .false.
124124

125125
!> Language features
126-
type(fortran_features_t) :: features
126+
type(fortran_config_t) :: features
127127

128128
!> Targets in the same schedule group are guaranteed to be independent
129129
integer :: schedule = -1
@@ -570,7 +570,7 @@ type(build_target_ptr) function new_target(package, type, output_name, source, l
570570
character(*), intent(in) :: output_name
571571
type(srcfile_t), intent(in), optional :: source
572572
type(string_t), intent(in), optional :: link_libraries(:)
573-
type(fortran_features_t), intent(in), optional :: features
573+
type(fortran_config_t), intent(in), optional :: features
574574
type(preprocess_config_t), intent(in), optional :: preprocess
575575
type(version_t), intent(in), optional :: version
576576
character(*), intent(in), optional :: output_dir
@@ -607,7 +607,7 @@ subroutine add_new_target(targets, package, type, output_name, source, link_libr
607607
character(*), intent(in) :: output_name
608608
type(srcfile_t), intent(in), optional :: source
609609
type(string_t), intent(in), optional :: link_libraries(:)
610-
type(fortran_features_t), intent(in), optional :: features
610+
type(fortran_config_t), intent(in), optional :: features
611611
type(preprocess_config_t), intent(in), optional :: preprocess
612612
type(version_t), intent(in), optional :: version
613613
character(*), intent(in), optional :: output_dir
@@ -1419,7 +1419,7 @@ end subroutine filter_modules
14191419

14201420
function get_feature_flags(compiler, features) result(flags)
14211421
type(compiler_t), intent(in) :: compiler
1422-
type(fortran_features_t), intent(in) :: features
1422+
type(fortran_config_t), intent(in) :: features
14231423
character(:), allocatable :: flags
14241424

14251425
flags = ""

src/metapackage/fpm_meta_base.f90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
module fpm_meta_base
22
use fpm_error, only: error_t, fatal_error
33
use fpm_versioning, only: version_t
4-
use fpm_model, only: fpm_model_t, fortran_features_t
4+
use fpm_model, only: fpm_model_t, fortran_config_t
55
use fpm_command_line, only: fpm_cmd_settings, fpm_run_settings
66
use fpm_manifest_dependency, only: dependency_config_t
77
use fpm_manifest_preprocess, only: preprocess_config_t
@@ -47,7 +47,7 @@ module fpm_meta_base
4747
type(string_t), allocatable :: external_modules(:)
4848

4949
!> Special fortran features
50-
type(fortran_features_t), allocatable :: fortran
50+
type(fortran_config_t), allocatable :: fortran
5151

5252
!> Preprocessor configuration
5353
type(preprocess_config_t), allocatable :: preprocess

test/fpm_test/test_toml.f90

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,7 @@ module test_toml
2020
use fpm_manifest_profile, only: file_scope_flag
2121
use fpm_versioning, only: new_version
2222
use fpm_strings, only: string_t, operator(==), split
23-
use fpm_model, only: fortran_features_t, package_t, FPM_SCOPE_LIB, FPM_UNIT_MODULE, fpm_model_t, &
23+
use fpm_model, only: fortran_config_t, package_t, FPM_SCOPE_LIB, FPM_UNIT_MODULE, fpm_model_t, &
2424
& srcfile_t
2525
use fpm_compiler, only: archiver_t, compiler_t, id_gcc
2626
use fpm_error, only: fatal_error
@@ -605,15 +605,15 @@ subroutine fft_roundtrip(error)
605605
!> Error handling
606606
type(error_t), allocatable, intent(out) :: error
607607

608-
type(fortran_features_t) :: fortran
608+
type(fortran_config_t) :: fortran
609609

610610
!> Default object
611-
call fortran%test_serialization('fortran_features_t: default object',error)
611+
call fortran%test_serialization('fortran_config_t: default object',error)
612612
if (allocated(error)) return
613613

614614
!> Set form
615615
fortran%source_form = "free"
616-
call fortran%test_serialization('fortran_features_t: with form',error)
616+
call fortran%test_serialization('fortran_config_t: with form',error)
617617
if (allocated(error)) return
618618

619619
end subroutine fft_roundtrip
@@ -624,7 +624,7 @@ subroutine fft_invalid(error)
624624
!> Error handling
625625
type(error_t), allocatable, intent(out) :: error
626626

627-
type(fortran_features_t) :: fortran
627+
type(fortran_config_t) :: fortran
628628
type(toml_table), allocatable :: table
629629

630630
character(len=*), parameter :: toml = 'implicit-typing = false '//NL//&

0 commit comments

Comments
 (0)