@@ -6,16 +6,16 @@ module fpm
6
6
use fpm_dependency, only : new_dependency_tree
7
7
use fpm_environment, only: run
8
8
use fpm_filesystem, only: is_dir, join_path, number_of_rows, list_files, exists, basename
9
- use fpm_model, only: fpm_model_t, srcfile_t, build_target_t , &
9
+ use fpm_model, only: fpm_model_t, srcfile_t, show_model , &
10
10
FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, FPM_SCOPE_DEP, &
11
- FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST, &
12
- FPM_TARGET_EXECUTABLE, FPM_TARGET_ARCHIVE, show_model
11
+ FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST
13
12
use fpm_compiler, only: add_compile_flag_defaults
14
13
15
14
16
15
use fpm_sources, only: add_executable_sources, add_sources_from_dir
17
16
use fpm_targets, only: targets_from_sources, resolve_module_dependencies, &
18
- resolve_target_linking
17
+ resolve_target_linking, build_target_t, build_target_ptr, &
18
+ FPM_TARGET_EXECUTABLE, FPM_TARGET_ARCHIVE
19
19
use fpm_manifest, only : get_package_data, package_config_t
20
20
use fpm_error, only : error_t, fatal_error
21
21
use fpm_manifest_test, only : test_config_t
@@ -50,11 +50,7 @@ subroutine build_model(model, settings, package, error)
50
50
51
51
model% package_name = package% name
52
52
53
- if (allocated (package% build% link)) then
54
- model% link_libraries = package% build% link
55
- else
56
- allocate (model% link_libraries(0 ))
57
- end if
53
+ allocate (model% link_libraries(0 ))
58
54
59
55
call new_dependency_tree(model% deps, cache= join_path(" build" , " cache.toml" ))
60
56
call model% deps% add(package, error)
@@ -73,8 +69,6 @@ subroutine build_model(model, settings, package, error)
73
69
write (* ,* )' <INFO>COMPILER OPTIONS: ' , model% fortran_compile_flags
74
70
endif
75
71
76
- model% link_flags = ' '
77
-
78
72
allocate (model% packages(model% deps% ndep))
79
73
80
74
! Add sources from executable directories
@@ -160,27 +154,14 @@ subroutine build_model(model, settings, package, error)
160
154
end do
161
155
if (allocated (error)) return
162
156
163
- call targets_from_sources(model)
164
-
165
- do i = 1 , size (model% link_libraries)
166
- model% link_flags = model% link_flags // " -l" // model% link_libraries(i)% s
167
- end do
168
-
169
- if (model% targets(1 )% ptr% target_type == FPM_TARGET_ARCHIVE) then
170
- model% library_file = model% targets(1 )% ptr% output_file
171
- end if
172
-
173
- call resolve_module_dependencies(model% targets,error)
174
-
175
- call resolve_target_linking(model% targets)
176
-
177
157
end subroutine build_model
178
158
179
159
180
160
subroutine cmd_build (settings )
181
161
type (fpm_build_settings), intent (in ) :: settings
182
162
type (package_config_t) :: package
183
163
type (fpm_model_t) :: model
164
+ type (build_target_ptr), allocatable :: targets(:)
184
165
type (error_t), allocatable :: error
185
166
186
167
integer :: i
@@ -197,14 +178,20 @@ subroutine cmd_build(settings)
197
178
error stop 1
198
179
end if
199
180
181
+ call targets_from_sources(targets,model,error)
182
+ if (allocated (error)) then
183
+ print ' (a)' , error% message
184
+ error stop 1
185
+ end if
186
+
200
187
if (settings% list)then
201
- do i= 1 ,size (model % targets)
202
- write (stderr,* ) model % targets(i)% ptr% output_file
188
+ do i= 1 ,size (targets)
189
+ write (stderr,* ) targets(i)% ptr% output_file
203
190
enddo
204
191
else if (settings% show_model) then
205
192
call show_model(model)
206
193
else
207
- call build_package(model)
194
+ call build_package(targets, model)
208
195
endif
209
196
210
197
end subroutine
@@ -218,6 +205,7 @@ subroutine cmd_run(settings,test)
218
205
type (error_t), allocatable :: error
219
206
type (package_config_t) :: package
220
207
type (fpm_model_t) :: model
208
+ type (build_target_ptr), allocatable :: targets(:)
221
209
type (string_t) :: exe_cmd
222
210
type (string_t), allocatable :: executables(:)
223
211
type (build_target_t), pointer :: exe_target
@@ -238,6 +226,12 @@ subroutine cmd_run(settings,test)
238
226
error stop 1
239
227
end if
240
228
229
+ call targets_from_sources(targets,model,error)
230
+ if (allocated (error)) then
231
+ print ' (a)' , error% message
232
+ error stop 1
233
+ end if
234
+
241
235
if (test) then
242
236
run_scope = FPM_SCOPE_TEST
243
237
else
@@ -248,9 +242,9 @@ subroutine cmd_run(settings,test)
248
242
col_width = - 1
249
243
found(:) = .false.
250
244
allocate (executables(0 ))
251
- do i= 1 ,size (model % targets)
245
+ do i= 1 ,size (targets)
252
246
253
- exe_target = > model % targets(i)% ptr
247
+ exe_target = > targets(i)% ptr
254
248
255
249
if (exe_target% target_type == FPM_TARGET_EXECUTABLE .and. &
256
250
allocated (exe_target% dependencies)) then
@@ -331,7 +325,7 @@ subroutine cmd_run(settings,test)
331
325
332
326
end if
333
327
334
- call build_package(model)
328
+ call build_package(targets, model)
335
329
336
330
if (settings% list) then
337
331
call compact_list()
@@ -357,9 +351,9 @@ subroutine compact_list_all()
357
351
j = 1
358
352
nCol = LINE_WIDTH/ col_width
359
353
write (stderr,* ) ' Available names:'
360
- do i= 1 ,size (model % targets)
354
+ do i= 1 ,size (targets)
361
355
362
- exe_target = > model % targets(i)% ptr
356
+ exe_target = > targets(i)% ptr
363
357
364
358
if (exe_target% target_type == FPM_TARGET_EXECUTABLE .and. &
365
359
allocated (exe_target% dependencies)) then
0 commit comments