Skip to content

Commit 79d7fb6

Browse files
authored
Merge pull request #369 from LKedward/separate-targets
Separate build targets from model structure
2 parents 32c96e5 + 0f5f02d commit 79d7fb6

File tree

9 files changed

+272
-344
lines changed

9 files changed

+272
-344
lines changed

fpm/fpm.toml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
name = "fpm"
2-
version = "0.1.3"
2+
version = "0.1.4"
33
license = "MIT"
44
author = "fpm maintainers"
55
maintainer = ""

fpm/src/fpm.f90

Lines changed: 27 additions & 33 deletions
Original file line numberDiff line numberDiff line change
@@ -6,16 +6,16 @@ module fpm
66
use fpm_dependency, only : new_dependency_tree
77
use fpm_environment, only: run
88
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, &
1010
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
1312
use fpm_compiler, only: add_compile_flag_defaults
1413

1514

1615
use fpm_sources, only: add_executable_sources, add_sources_from_dir
1716
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
1919
use fpm_manifest, only : get_package_data, package_config_t
2020
use fpm_error, only : error_t, fatal_error
2121
use fpm_manifest_test, only : test_config_t
@@ -50,11 +50,7 @@ subroutine build_model(model, settings, package, error)
5050

5151
model%package_name = package%name
5252

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))
5854

5955
call new_dependency_tree(model%deps, cache=join_path("build", "cache.toml"))
6056
call model%deps%add(package, error)
@@ -73,8 +69,6 @@ subroutine build_model(model, settings, package, error)
7369
write(*,*)'<INFO>COMPILER OPTIONS: ', model%fortran_compile_flags
7470
endif
7571

76-
model%link_flags = ''
77-
7872
allocate(model%packages(model%deps%ndep))
7973

8074
! Add sources from executable directories
@@ -160,27 +154,14 @@ subroutine build_model(model, settings, package, error)
160154
end do
161155
if (allocated(error)) return
162156

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-
177157
end subroutine build_model
178158

179159

180160
subroutine cmd_build(settings)
181161
type(fpm_build_settings), intent(in) :: settings
182162
type(package_config_t) :: package
183163
type(fpm_model_t) :: model
164+
type(build_target_ptr), allocatable :: targets(:)
184165
type(error_t), allocatable :: error
185166

186167
integer :: i
@@ -197,14 +178,20 @@ subroutine cmd_build(settings)
197178
error stop 1
198179
end if
199180

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+
200187
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
203190
enddo
204191
else if (settings%show_model) then
205192
call show_model(model)
206193
else
207-
call build_package(model)
194+
call build_package(targets,model)
208195
endif
209196

210197
end subroutine
@@ -218,6 +205,7 @@ subroutine cmd_run(settings,test)
218205
type(error_t), allocatable :: error
219206
type(package_config_t) :: package
220207
type(fpm_model_t) :: model
208+
type(build_target_ptr), allocatable :: targets(:)
221209
type(string_t) :: exe_cmd
222210
type(string_t), allocatable :: executables(:)
223211
type(build_target_t), pointer :: exe_target
@@ -238,6 +226,12 @@ subroutine cmd_run(settings,test)
238226
error stop 1
239227
end if
240228

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+
241235
if (test) then
242236
run_scope = FPM_SCOPE_TEST
243237
else
@@ -248,9 +242,9 @@ subroutine cmd_run(settings,test)
248242
col_width = -1
249243
found(:) = .false.
250244
allocate(executables(0))
251-
do i=1,size(model%targets)
245+
do i=1,size(targets)
252246

253-
exe_target => model%targets(i)%ptr
247+
exe_target => targets(i)%ptr
254248

255249
if (exe_target%target_type == FPM_TARGET_EXECUTABLE .and. &
256250
allocated(exe_target%dependencies)) then
@@ -331,7 +325,7 @@ subroutine cmd_run(settings,test)
331325

332326
end if
333327

334-
call build_package(model)
328+
call build_package(targets,model)
335329

336330
if (settings%list) then
337331
call compact_list()
@@ -357,9 +351,9 @@ subroutine compact_list_all()
357351
j = 1
358352
nCol = LINE_WIDTH/col_width
359353
write(stderr,*) 'Available names:'
360-
do i=1,size(model%targets)
354+
do i=1,size(targets)
361355

362-
exe_target => model%targets(i)%ptr
356+
exe_target => targets(i)%ptr
363357

364358
if (exe_target%target_type == FPM_TARGET_EXECUTABLE .and. &
365359
allocated(exe_target%dependencies)) then

fpm/src/fpm/cmd/install.f90

Lines changed: 20 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -7,8 +7,9 @@ module fpm_cmd_install
77
use fpm_filesystem, only : join_path, list_files
88
use fpm_installer, only : installer_t, new_installer
99
use fpm_manifest, only : package_config_t, get_package_data
10-
use fpm_model, only : fpm_model_t, build_target_t, FPM_TARGET_EXECUTABLE, &
11-
FPM_SCOPE_APP
10+
use fpm_model, only : fpm_model_t, FPM_SCOPE_APP
11+
use fpm_targets, only: targets_from_sources, build_target_t, &
12+
build_target_ptr, FPM_TARGET_EXECUTABLE
1213
use fpm_strings, only : string_t, resize
1314
implicit none
1415
private
@@ -24,6 +25,7 @@ subroutine cmd_install(settings)
2425
type(package_config_t) :: package
2526
type(error_t), allocatable :: error
2627
type(fpm_model_t) :: model
28+
type(build_target_ptr), allocatable :: targets(:)
2729
type(installer_t) :: installer
2830
character(len=:), allocatable :: lib, exe, dir
2931
logical :: installable
@@ -34,6 +36,9 @@ subroutine cmd_install(settings)
3436
call build_model(model, settings%fpm_build_settings, package, error)
3537
call handle_error(error)
3638

39+
call targets_from_sources(targets,model,error)
40+
call handle_error(error)
41+
3742
installable = (allocated(package%library) .and. package%install%library) &
3843
.or. allocated(package%executable)
3944
if (.not.installable) then
@@ -42,12 +47,12 @@ subroutine cmd_install(settings)
4247
end if
4348

4449
if (settings%list) then
45-
call install_info(output_unit, package, model)
50+
call install_info(output_unit, package, model, targets)
4651
return
4752
end if
4853

4954
if (.not.settings%no_rebuild) then
50-
call build_package(model)
55+
call build_package(targets,model)
5156
end if
5257

5358
call new_installer(installer, prefix=settings%prefix, &
@@ -66,16 +71,17 @@ subroutine cmd_install(settings)
6671
end if
6772

6873
if (allocated(package%executable)) then
69-
call install_executables(installer, model, error)
74+
call install_executables(installer, targets, error)
7075
call handle_error(error)
7176
end if
7277

7378
end subroutine cmd_install
7479

75-
subroutine install_info(unit, package, model)
80+
subroutine install_info(unit, package, model, targets)
7681
integer, intent(in) :: unit
7782
type(package_config_t), intent(in) :: package
7883
type(fpm_model_t), intent(in) :: model
84+
type(build_target_ptr), intent(in) :: targets(:)
7985

8086
integer :: ii, ntargets
8187
character(len=:), allocatable :: lib
@@ -90,11 +96,11 @@ subroutine install_info(unit, package, model)
9096
"lib"//model%package_name//".a")
9197
install_target(ntargets)%s = lib
9298
end if
93-
do ii = 1, size(model%targets)
94-
if (is_executable_target(model%targets(ii)%ptr)) then
99+
do ii = 1, size(targets)
100+
if (is_executable_target(targets(ii)%ptr)) then
95101
if (ntargets >= size(install_target)) call resize(install_target)
96102
ntargets = ntargets + 1
97-
install_target(ntargets)%s = model%targets(ii)%ptr%output_file
103+
install_target(ntargets)%s = targets(ii)%ptr%output_file
98104
end if
99105
end do
100106

@@ -125,15 +131,15 @@ subroutine install_module_files(installer, dir, error)
125131

126132
end subroutine install_module_files
127133

128-
subroutine install_executables(installer, model, error)
134+
subroutine install_executables(installer, targets, error)
129135
type(installer_t), intent(inout) :: installer
130-
type(fpm_model_t), intent(in) :: model
136+
type(build_target_ptr), intent(in) :: targets(:)
131137
type(error_t), allocatable, intent(out) :: error
132138
integer :: ii
133139

134-
do ii = 1, size(model%targets)
135-
if (is_executable_target(model%targets(ii)%ptr)) then
136-
call installer%install_executable(model%targets(ii)%ptr%output_file, error)
140+
do ii = 1, size(targets)
141+
if (is_executable_target(targets(ii)%ptr)) then
142+
call installer%install_executable(targets(ii)%ptr%output_file, error)
137143
if (allocated(error)) exit
138144
end if
139145
end do

fpm/src/fpm_backend.f90

Lines changed: 13 additions & 25 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
!># Build backend
2-
!> Uses a valid `[[fpm_model]]` instance to schedule and execute the
3-
!> compilation and linking of package targets.
2+
!> Uses a list of `[[build_target_ptr]]` and a valid `[[fpm_model]]` instance
3+
!> to schedule and execute the compilation and linking of package targets.
44
!>
55
!> The package build process (`[[build_package]]`) comprises three steps:
66
!>
@@ -29,7 +29,8 @@ module fpm_backend
2929

3030
use fpm_environment, only: run
3131
use fpm_filesystem, only: dirname, join_path, exists, mkdir
32-
use fpm_model, only: fpm_model_t, build_target_t, build_target_ptr, &
32+
use fpm_model, only: fpm_model_t
33+
use fpm_targets, only: build_target_t, build_target_ptr, &
3334
FPM_TARGET_OBJECT, FPM_TARGET_ARCHIVE, FPM_TARGET_EXECUTABLE
3435

3536
use fpm_strings, only: string_cat
@@ -42,8 +43,9 @@ module fpm_backend
4243
contains
4344

4445
!> Top-level routine to build package described by `model`
45-
subroutine build_package(model)
46-
type(fpm_model_t), intent(inout) :: model
46+
subroutine build_package(targets,model)
47+
type(build_target_ptr), intent(inout) :: targets(:)
48+
type(fpm_model_t), intent(in) :: model
4749

4850
integer :: i, j
4951
type(build_target_ptr), allocatable :: queue(:)
@@ -55,14 +57,14 @@ subroutine build_package(model)
5557
end if
5658

5759
! Perform depth-first topological sort of targets
58-
do i=1,size(model%targets)
60+
do i=1,size(targets)
5961

60-
call sort_target(model%targets(i)%ptr)
62+
call sort_target(targets(i)%ptr)
6163

6264
end do
6365

6466
! Construct build schedule queue
65-
call schedule_targets(queue, schedule_ptr, model%targets)
67+
call schedule_targets(queue, schedule_ptr, targets)
6668

6769
! Loop over parallel schedule regions
6870
do i=1,size(schedule_ptr)-1
@@ -236,27 +238,13 @@ subroutine build_target(model,target)
236238
select case(target%target_type)
237239

238240
case (FPM_TARGET_OBJECT)
239-
call run(model%fortran_compiler//" -c " // target%source%file_name // model%fortran_compile_flags &
241+
call run(model%fortran_compiler//" -c " // target%source%file_name // target%compile_flags &
240242
// " -o " // target%output_file)
241243

242244
case (FPM_TARGET_EXECUTABLE)
243-
244-
link_flags = string_cat(target%link_objects," ")
245-
246-
if (allocated(model%library_file)) then
247-
link_flags = link_flags//" "//model%library_file//" "//model%link_flags
248-
else
249-
link_flags = link_flags//" "//model%link_flags
250-
end if
251-
252-
if (allocated(target%link_libraries)) then
253-
if (size(target%link_libraries) > 0) then
254-
link_flags = link_flags // " -l" // string_cat(target%link_libraries," -l")
255-
end if
256-
end if
257245

258-
call run(model%fortran_compiler// " " // model%fortran_compile_flags &
259-
//" "//link_flags// " -o " // target%output_file)
246+
call run(model%fortran_compiler// " " // target%compile_flags &
247+
//" "//target%link_flags// " -o " // target%output_file)
260248

261249
case (FPM_TARGET_ARCHIVE)
262250
call run("ar -rs " // target%output_file // " " // string_cat(target%link_objects," "))

fpm/src/fpm_command_line.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -130,7 +130,7 @@ subroutine get_command_line_settings(cmd_settings)
130130
case default ; os_type = "OS Type: UNKNOWN"
131131
end select
132132
version_text = [character(len=80) :: &
133-
& 'Version: 0.1.3, alpha', &
133+
& 'Version: 0.1.4, alpha', &
134134
& 'Program: fpm(1)', &
135135
& 'Description: A Fortran package manager and build system', &
136136
& 'Home Page: https://github.com/fortran-lang/fpm', &

0 commit comments

Comments
 (0)