@@ -16,7 +16,7 @@ module fpm
1616
1717
1818use fpm_sources, only: add_executable_sources, add_sources_from_dir
19- use fpm_targets, only: targets_from_sources, resolve_module_dependencies, &
19+ use fpm_targets, only: targets_from_sources, &
2020 resolve_target_linking, build_target_t, build_target_ptr, &
2121 FPM_TARGET_EXECUTABLE, FPM_TARGET_ARCHIVE
2222use fpm_manifest, only : get_package_data, package_config_t
@@ -101,6 +101,61 @@ subroutine build_model(model, settings, package, error)
101101
102102 allocate (model% packages(model% deps% ndep))
103103
104+ do i = 1 , model% deps% ndep
105+ associate(dep = > model% deps% dep(i))
106+ manifest = join_path(dep% proj_dir, " fpm.toml" )
107+
108+ call get_package_data(dependency, manifest, error, &
109+ apply_defaults= .true. )
110+ if (allocated (error)) exit
111+
112+ model% packages(i)% name = dependency% name
113+ call package% version% to_string(version)
114+ model% packages(i)% version = version
115+
116+ if (allocated (dependency% preprocess)) then
117+ do j = 1 , size (dependency% preprocess)
118+ if (package% preprocess(j)% name == " cpp" ) then
119+ model% packages(i)% macros = dependency% preprocess(j)% macros
120+ end if
121+ end do
122+ end if
123+
124+ if (.not. allocated (model% packages(i)% sources)) allocate (model% packages(i)% sources(0 ))
125+
126+ if (allocated (dependency% library)) then
127+
128+ if (allocated (dependency% library% source_dir)) then
129+ lib_dir = join_path(dep% proj_dir, dependency% library% source_dir)
130+ if (is_dir(lib_dir)) then
131+ call add_sources_from_dir(model% packages(i)% sources, lib_dir, FPM_SCOPE_LIB, &
132+ error= error)
133+ if (allocated (error)) exit
134+ end if
135+ end if
136+
137+ if (allocated (dependency% library% include_dir)) then
138+ do j= 1 ,size (dependency% library% include_dir)
139+ include_dir% s = join_path(dep% proj_dir, dependency% library% include_dir(j)% s)
140+ if (is_dir(include_dir% s)) then
141+ model% include_dirs = [model% include_dirs, include_dir]
142+ end if
143+ end do
144+ end if
145+
146+ end if
147+
148+ if (allocated (dependency% build% link)) then
149+ model% link_libraries = [model% link_libraries, dependency% build% link]
150+ end if
151+
152+ if (allocated (dependency% build% external_modules)) then
153+ model% external_modules = [model% external_modules, dependency% build% external_modules]
154+ end if
155+ end associate
156+ end do
157+ if (allocated (error)) return
158+
104159 ! Add sources from executable directories
105160 if (is_dir(' app' ) .and. package% build% auto_executables) then
106161 call add_sources_from_dir(model% packages(1 )% sources,' app' , FPM_SCOPE_APP, &
@@ -160,60 +215,6 @@ subroutine build_model(model, settings, package, error)
160215
161216 endif
162217
163- do i = 1 , model% deps% ndep
164- associate(dep = > model% deps% dep(i))
165- manifest = join_path(dep% proj_dir, " fpm.toml" )
166-
167- call get_package_data(dependency, manifest, error, &
168- apply_defaults= .true. )
169- if (allocated (error)) exit
170-
171- model% packages(i)% name = dependency% name
172- call package% version% to_string(version)
173- model% packages(i)% version = version
174-
175- if (allocated (dependency% preprocess)) then
176- do j = 1 , size (dependency% preprocess)
177- if (package% preprocess(j)% name == " cpp" ) then
178- model% packages(i)% macros = dependency% preprocess(j)% macros
179- end if
180- end do
181- end if
182-
183- if (.not. allocated (model% packages(i)% sources)) allocate (model% packages(i)% sources(0 ))
184-
185- if (allocated (dependency% library)) then
186-
187- if (allocated (dependency% library% source_dir)) then
188- lib_dir = join_path(dep% proj_dir, dependency% library% source_dir)
189- if (is_dir(lib_dir)) then
190- call add_sources_from_dir(model% packages(i)% sources, lib_dir, FPM_SCOPE_LIB, &
191- error= error)
192- if (allocated (error)) exit
193- end if
194- end if
195-
196- if (allocated (dependency% library% include_dir)) then
197- do j= 1 ,size (dependency% library% include_dir)
198- include_dir% s = join_path(dep% proj_dir, dependency% library% include_dir(j)% s)
199- if (is_dir(include_dir% s)) then
200- model% include_dirs = [model% include_dirs, include_dir]
201- end if
202- end do
203- end if
204-
205- end if
206-
207- if (allocated (dependency% build% link)) then
208- model% link_libraries = [model% link_libraries, dependency% build% link]
209- end if
210-
211- if (allocated (dependency% build% external_modules)) then
212- model% external_modules = [model% external_modules, dependency% build% external_modules]
213- end if
214- end associate
215- end do
216- if (allocated (error)) return
217218
218219 if (settings% verbose) then
219220 write (* ,* )' <INFO> BUILD_NAME: ' ,model% build_prefix
0 commit comments