Skip to content

Commit beaf9a8

Browse files
committed
Enable multiple build output directories
1 parent dfeb17a commit beaf9a8

File tree

8 files changed

+196
-69
lines changed

8 files changed

+196
-69
lines changed

src/fpm.f90

+5-8
Original file line numberDiff line numberDiff line change
@@ -43,7 +43,6 @@ subroutine build_model(model, settings, package, error)
4343

4444
logical :: duplicates_found = .false.
4545
type(string_t) :: include_dir
46-
character(len=16) :: build_name
4746

4847
model%package_name = package%name
4948

@@ -72,21 +71,19 @@ subroutine build_model(model, settings, package, error)
7271
flags = flags // model%compiler%get_default_flags(settings%profile == "release")
7372
end select
7473
end if
75-
7674
cflags = trim(settings%cflag)
7775
ldflags = trim(settings%ldflag)
7876

79-
write(build_name, '(z16.16)') fnv_1a(flags//cflags//ldflags)
80-
8177
if (model%compiler%is_unknown()) then
8278
write(*, '(*(a:,1x))') &
8379
"<WARN>", "Unknown compiler", model%compiler%fc, "requested!", &
8480
"Defaults for this compiler might be incorrect"
8581
end if
86-
model%output_directory = join_path('build',basename(model%compiler%fc)//'_'//build_name)
82+
model%build_prefix = join_path("build", basename(model%compiler%fc))
8783

88-
model%fortran_compile_flags = flags // " " // &
89-
& model%compiler%get_module_flag(join_path(model%output_directory, model%package_name))
84+
model%fortran_compile_flags = flags
85+
model%c_compile_flags = cflags
86+
model%link_flags = ldflags
9087

9188
model%include_tests = settings%build_tests
9289

@@ -196,7 +193,7 @@ subroutine build_model(model, settings, package, error)
196193
if (allocated(error)) return
197194

198195
if (settings%verbose) then
199-
write(*,*)'<INFO> BUILD_NAME: ',build_name
196+
write(*,*)'<INFO> BUILD_NAME: ',model%build_prefix
200197
write(*,*)'<INFO> COMPILER: ',model%compiler%fc
201198
write(*,*)'<INFO> C COMPILER: ',model%compiler%cc
202199
write(*,*)'<INFO> COMPILER OPTIONS: ', model%fortran_compile_flags

src/fpm/cmd/install.f90

+20-23
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,8 @@ module fpm_cmd_install
99
use fpm_manifest, only : package_config_t, get_package_data
1010
use fpm_model, only : fpm_model_t, FPM_SCOPE_APP
1111
use fpm_targets, only: targets_from_sources, build_target_t, &
12-
build_target_ptr, FPM_TARGET_EXECUTABLE
12+
build_target_ptr, FPM_TARGET_EXECUTABLE, &
13+
filter_library_targets, filter_executable_targets
1314
use fpm_strings, only : string_t, resize
1415
implicit none
1516
private
@@ -28,6 +29,7 @@ subroutine cmd_install(settings)
2829
type(build_target_ptr), allocatable :: targets(:)
2930
type(installer_t) :: installer
3031
character(len=:), allocatable :: lib, dir
32+
type(string_t), allocatable :: list(:)
3133
logical :: installable
3234

3335
call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
@@ -61,13 +63,15 @@ subroutine cmd_install(settings)
6163
verbosity=merge(2, 1, settings%verbose))
6264

6365
if (allocated(package%library) .and. package%install%library) then
64-
dir = join_path(model%output_directory, model%package_name)
65-
lib = "lib"//model%package_name//".a"
66-
call installer%install_library(join_path(dir, lib), error)
67-
call handle_error(error)
66+
call filter_library_targets(targets, list)
6867

69-
call install_module_files(installer, dir, error)
70-
call handle_error(error)
68+
if (size(list) > 0) then
69+
call installer%install_library(list(1)%s, error)
70+
call handle_error(error)
71+
72+
call install_module_files(installer, dir, error)
73+
call handle_error(error)
74+
end if
7175
end if
7276

7377
if (allocated(package%executable)) then
@@ -85,24 +89,17 @@ subroutine install_info(unit, package, model, targets)
8589

8690
integer :: ii, ntargets
8791
character(len=:), allocatable :: lib
88-
type(string_t), allocatable :: install_target(:)
92+
type(string_t), allocatable :: install_target(:), temp(:)
8993

90-
call resize(install_target)
94+
allocate(install_target(0))
9195

92-
ntargets = 0
93-
if (allocated(package%library) .and. package%install%library) then
94-
ntargets = ntargets + 1
95-
lib = join_path(model%output_directory, model%package_name, &
96-
"lib"//model%package_name//".a")
97-
install_target(ntargets)%s = lib
98-
end if
99-
do ii = 1, size(targets)
100-
if (is_executable_target(targets(ii)%ptr)) then
101-
if (ntargets >= size(install_target)) call resize(install_target)
102-
ntargets = ntargets + 1
103-
install_target(ntargets)%s = targets(ii)%ptr%output_file
104-
end if
105-
end do
96+
call filter_library_targets(targets, temp)
97+
install_target = [install_target, temp]
98+
99+
call filter_executable_targets(targets, FPM_SCOPE_APP, temp)
100+
install_target = [install_target, temp]
101+
102+
ntargets = size(install_target)
106103

107104
write(unit, '("#", *(1x, g0))') &
108105
"total number of installable targets:", ntargets

src/fpm_backend.f90

+18-3
Original file line numberDiff line numberDiff line change
@@ -32,6 +32,7 @@ module fpm_backend
3232
use fpm_environment, only: run, get_os_type, OS_WINDOWS
3333
use fpm_filesystem, only: basename, dirname, join_path, exists, mkdir
3434
use fpm_model, only: fpm_model_t
35+
use fpm_strings, only: string_t, operator(.in.)
3536
use fpm_targets, only: build_target_t, build_target_ptr, FPM_TARGET_OBJECT, &
3637
FPM_TARGET_C_OBJECT, FPM_TARGET_ARCHIVE, FPM_TARGET_EXECUTABLE
3738
implicit none
@@ -50,11 +51,25 @@ subroutine build_package(targets,model)
5051
type(build_target_ptr), allocatable :: queue(:)
5152
integer, allocatable :: schedule_ptr(:), stat(:)
5253
logical :: build_failed, skip_current
54+
type(string_t), allocatable :: build_dirs(:)
55+
type(string_t) :: temp
5356

5457
! Need to make output directory for include (mod) files
55-
if (.not.exists(join_path(model%output_directory,model%package_name))) then
56-
call mkdir(join_path(model%output_directory,model%package_name))
57-
end if
58+
!if (.not.exists(join_path(model%output_directory,model%package_name))) then
59+
!call mkdir(join_path(model%output_directory,model%package_name))
60+
!end if
61+
allocate(build_dirs(0))
62+
do i = 1, size(targets)
63+
associate(target => targets(i)%ptr)
64+
if (target%output_dir .in. build_dirs) cycle
65+
temp%s = target%output_dir
66+
build_dirs = [build_dirs, temp]
67+
end associate
68+
end do
69+
70+
do i = 1, size(build_dirs)
71+
call mkdir(build_dirs(i)%s)
72+
end do
5873

5974
! Perform depth-first topological sort of targets
6075
do i=1,size(targets)

src/fpm_compiler.f90

-1
Original file line numberDiff line numberDiff line change
@@ -417,7 +417,6 @@ function get_module_flag(self, path) result(flags)
417417
flags = "-qmoddir "//path
418418

419419
end select
420-
flags = flags//" "//self%get_include_flag(path)
421420

422421
end function get_module_flag
423422

src/fpm_model.f90

+2-3
Original file line numberDiff line numberDiff line change
@@ -131,7 +131,7 @@ module fpm_model
131131
character(:), allocatable :: link_flags
132132

133133
!> Base directory for build
134-
character(:), allocatable :: output_directory
134+
character(:), allocatable :: build_prefix
135135

136136
!> Include directories
137137
type(string_t), allocatable :: include_dirs(:)
@@ -284,8 +284,7 @@ function info_model(model) result(s)
284284
s = s // ', fortran_compile_flags="' // model%fortran_compile_flags // '"'
285285
s = s // ', c_compile_flags="' // model%c_compile_flags // '"'
286286
s = s // ', link_flags="' // model%link_flags // '"'
287-
! character(:), allocatable :: output_directory
288-
s = s // ', output_directory="' // model%output_directory // '"'
287+
s = s // ', build_prefix="' // model%build_prefix // '"'
289288
! type(string_t), allocatable :: link_libraries(:)
290289
s = s // ", link_libraries=["
291290
do i = 1, size(model%link_libraries)

0 commit comments

Comments
 (0)