@@ -46,10 +46,11 @@ module fpm_model
46
46
use fpm_error, only: error_t, fatal_error
47
47
use fpm_environment, only: OS_WINDOWS,OS_MACOS
48
48
use fpm_manifest_preprocess, only: preprocess_config_t
49
+ use fpm_manifest_fortran, only: fortran_config_t
49
50
implicit none
50
51
51
52
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
53
54
54
55
public :: FPM_UNIT_UNKNOWN, FPM_UNIT_PROGRAM, FPM_UNIT_MODULE, &
55
56
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, FPM_UNIT_CSOURCE, &
@@ -86,27 +87,6 @@ module fpm_model
86
87
integer , parameter :: FPM_SCOPE_TEST = 4
87
88
integer , parameter :: FPM_SCOPE_EXAMPLE = 5
88
89
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
-
110
90
! > Type for describing a source file
111
91
type, extends(serializable_t) :: srcfile_t
112
92
! > File path relative to cwd
@@ -171,7 +151,7 @@ module fpm_model
171
151
type (string_t) :: module_prefix
172
152
173
153
! > Language features
174
- type (fortran_features_t ) :: features
154
+ type (fortran_config_t ) :: features
175
155
176
156
contains
177
157
@@ -614,77 +594,6 @@ subroutine srcfile_load_from_toml(self, table, error)
614
594
615
595
end subroutine srcfile_load_from_toml
616
596
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
-
688
597
! > Check that two package objects are equal
689
598
logical function package_is_same (this ,that )
690
599
class(package_t), intent (in ) :: this
0 commit comments