@@ -40,12 +40,13 @@ module fpm
40
40
subroutine build_model (model , settings , package , error )
41
41
type (fpm_model_t), intent (out ) :: model
42
42
class(fpm_build_settings), intent (inout ) :: settings
43
- type (package_config_t), intent (inout ) :: package
43
+ type (package_config_t), intent (inout ), target :: package
44
44
type (error_t), allocatable , intent (out ) :: error
45
45
46
46
integer :: i, j
47
- type (package_config_t) :: dependency
48
- character (len= :), allocatable :: manifest, lib_dir
47
+ type (package_config_t), target :: dependency
48
+ type (package_config_t), pointer :: manifest
49
+ character (len= :), allocatable :: file_name, lib_dir
49
50
logical :: has_cpp
50
51
logical :: duplicates_found
51
52
type (string_t) :: include_dir
@@ -76,7 +77,7 @@ subroutine build_model(model, settings, package, error)
76
77
! Resolve meta-dependencies into the package and the model
77
78
call resolve_metapackages(model,package,settings,error)
78
79
if (allocated (error)) return
79
-
80
+
80
81
! Create dependencies
81
82
call new_dependency_tree(model% deps, cache= join_path(" build" , " cache.toml" ), &
82
83
& path_to_config= settings% path_to_config)
@@ -99,25 +100,32 @@ subroutine build_model(model, settings, package, error)
99
100
has_cpp = .false.
100
101
do i = 1 , model% deps% ndep
101
102
associate(dep = > model% deps% dep(i))
102
- manifest = join_path(dep% proj_dir, " fpm.toml" )
103
-
104
- call get_package_data(dependency, manifest, error, apply_defaults= .true. )
105
- if (allocated (error)) exit
103
+ file_name = join_path(dep% proj_dir, " fpm.toml" )
106
104
107
- model% packages(i)% name = dependency% name
105
+ ! The main package manifest should not be reloaded, because it may have been
106
+ ! affected by model dependencies and metapackages
107
+ if (i== 1 ) then
108
+ manifest = > package
109
+ else
110
+
111
+ call get_package_data(dependency, file_name, error, apply_defaults= .true. )
112
+ if (allocated (error)) exit
113
+
114
+ manifest = > dependency
115
+ end if
116
+
117
+ model% packages(i)% name = manifest% name
108
118
associate(features = > model% packages(i)% features)
109
- features% implicit_typing = dependency % fortran% implicit_typing
110
- features% implicit_external = dependency % fortran% implicit_external
111
- features% source_form = dependency % fortran% source_form
119
+ features% implicit_typing = manifest % fortran% implicit_typing
120
+ features% implicit_external = manifest % fortran% implicit_external
121
+ features% source_form = manifest % fortran% source_form
112
122
end associate
113
123
model% packages(i)% version = package% version% s()
114
124
115
125
! > Add this dependency's manifest macros
116
- call model% packages(i)% preprocess% destroy()
117
-
118
- if (allocated (dependency% preprocess)) then
119
- do j = 1 , size (dependency% preprocess)
120
- call model% packages(i)% preprocess% add_config(dependency% preprocess(j))
126
+ if (allocated (manifest% preprocess)) then
127
+ do j = 1 , size (manifest% preprocess)
128
+ call model% packages(i)% preprocess% add_config(manifest% preprocess(j))
121
129
end do
122
130
end if
123
131
@@ -132,20 +140,20 @@ subroutine build_model(model, settings, package, error)
132
140
133
141
if (.not. allocated (model% packages(i)% sources)) allocate (model% packages(i)% sources(0 ))
134
142
135
- if (allocated (dependency % library)) then
143
+ if (allocated (manifest % library)) then
136
144
137
- if (allocated (dependency % library% source_dir)) then
138
- lib_dir = join_path(dep% proj_dir, dependency % library% source_dir)
145
+ if (allocated (manifest % library% source_dir)) then
146
+ lib_dir = join_path(dep% proj_dir, manifest % library% source_dir)
139
147
if (is_dir(lib_dir)) then
140
148
call add_sources_from_dir(model% packages(i)% sources, lib_dir, FPM_SCOPE_LIB, &
141
149
with_f_ext= model% packages(i)% preprocess% suffixes, error= error)
142
150
if (allocated (error)) exit
143
151
end if
144
152
end if
145
153
146
- if (allocated (dependency % library% include_dir)) then
147
- do j= 1 ,size (dependency % library% include_dir)
148
- include_dir% s = join_path(dep% proj_dir, dependency % library% include_dir(j)% s)
154
+ if (allocated (manifest % library% include_dir)) then
155
+ do j= 1 ,size (manifest % library% include_dir)
156
+ include_dir% s = join_path(dep% proj_dir, manifest % library% include_dir(j)% s)
149
157
if (is_dir(include_dir% s)) then
150
158
model% include_dirs = [model% include_dirs, include_dir]
151
159
end if
@@ -154,17 +162,17 @@ subroutine build_model(model, settings, package, error)
154
162
155
163
end if
156
164
157
- if (allocated (dependency % build% link)) then
158
- model% link_libraries = [model% link_libraries, dependency % build% link]
165
+ if (allocated (manifest % build% link)) then
166
+ model% link_libraries = [model% link_libraries, manifest % build% link]
159
167
end if
160
168
161
- if (allocated (dependency % build% external_modules)) then
162
- model% external_modules = [model% external_modules, dependency % build% external_modules]
169
+ if (allocated (manifest % build% external_modules)) then
170
+ model% external_modules = [model% external_modules, manifest % build% external_modules]
163
171
end if
164
172
165
173
! Copy naming conventions from this dependency's manifest
166
- model% packages(i)% enforce_module_names = dependency % build% module_naming
167
- model% packages(i)% module_prefix = dependency % build% module_prefix
174
+ model% packages(i)% enforce_module_names = manifest % build% module_naming
175
+ model% packages(i)% module_prefix = manifest % build% module_prefix
168
176
169
177
end associate
170
178
end do
0 commit comments