Skip to content

Commit db42238

Browse files
committed
targets: always initialize an output_dir
1 parent 01fb0b5 commit db42238

File tree

4 files changed

+45
-18
lines changed

4 files changed

+45
-18
lines changed

src/fpm/cmd/export.f90

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -22,7 +22,6 @@ subroutine cmd_export(settings)
2222
type(fpm_model_t) :: model
2323
type(error_t), allocatable :: error
2424

25-
integer :: ii
2625
character(len=:), allocatable :: filename
2726

2827
if (len_trim(settings%dump_manifest)<=0 .and. &

src/fpm_targets.f90

Lines changed: 28 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -140,6 +140,9 @@ module fpm_targets
140140

141141
!> Print information on this instance
142142
procedure :: info
143+
144+
!> Set output directory
145+
procedure :: set_output_dir
143146

144147
procedure :: is_executable_target
145148

@@ -554,7 +557,7 @@ end subroutine collect_exe_link_dependencies
554557

555558
!> Allocate a new target and append to target list
556559
subroutine add_target(targets, package, type, output_name, source, link_libraries, &
557-
& features, preprocess, version)
560+
& features, preprocess, version, output_dir)
558561
type(build_target_ptr), allocatable, intent(inout) :: targets(:)
559562
character(*), intent(in) :: package
560563
integer, intent(in) :: type
@@ -564,6 +567,7 @@ subroutine add_target(targets, package, type, output_name, source, link_librarie
564567
type(fortran_features_t), intent(in), optional :: features
565568
type(preprocess_config_t), intent(in), optional :: preprocess
566569
character(*), intent(in), optional :: version
570+
character(*), intent(in), optional :: output_dir
567571

568572
integer :: i
569573
type(build_target_t), pointer :: new_target
@@ -596,6 +600,9 @@ subroutine add_target(targets, package, type, output_name, source, link_librarie
596600
endif
597601
if (present(version)) new_target%version = version
598602
allocate(new_target%dependencies(0))
603+
604+
call new_target%set_output_dir(output_dir)
605+
599606

600607
targets = [targets, build_target_ptr(new_target)]
601608

@@ -1010,9 +1017,8 @@ subroutine resolve_target_linking(targets, model, library, error)
10101017
if (len(global_include_flags) > 0) then
10111018
target%compile_flags = target%compile_flags//global_include_flags
10121019
end if
1013-
target%output_dir = get_output_dir(model%build_prefix, target%compile_flags)
1014-
target%output_log_file = join_path(target%output_dir, target%output_name)//'.log'
1015-
target%output_file = join_path(target%output_dir, target%output_name)
1020+
1021+
call target%set_output_dir(get_output_dir(model%build_prefix, target%compile_flags))
10161022

10171023
! Check shared build
10181024
if (target%target_type==FPM_TARGET_SHARED) shared = .true.
@@ -1358,4 +1364,22 @@ function get_feature_flags(compiler, features) result(flags)
13581364
end if
13591365
end function get_feature_flags
13601366

1367+
!> Helper function: update output directory of a target
1368+
subroutine set_output_dir(self, output_dir)
1369+
class(build_target_t), intent(inout) :: self
1370+
character(*), optional, intent(in) :: output_dir
1371+
1372+
character(:), allocatable :: outdir
1373+
1374+
! Normalize: if output_dir is empty, use no path
1375+
outdir = ""
1376+
if (present(output_dir)) outdir = trim(output_dir)
1377+
1378+
self%output_dir = outdir
1379+
self%output_file = join_path(outdir, self%output_name)
1380+
self%output_log_file = self%output_file // ".log"
1381+
1382+
end subroutine set_output_dir
1383+
1384+
13611385
end module fpm_targets

test/fpm_test/test_backend.f90

Lines changed: 0 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -355,10 +355,6 @@ function new_test_package() result(targets)
355355
call add_dependency(targets(2)%ptr,targets(4)%ptr)
356356
call add_dependency(targets(3)%ptr,targets(4)%ptr)
357357

358-
do i = 1, size(targets)
359-
targets(i)%ptr%output_file = targets(i)%ptr%output_name
360-
end do
361-
362358
end function new_test_package
363359

364360
subroutine compile_commands_roundtrip(error)
@@ -488,10 +484,6 @@ subroutine test_target_shared(error)
488484
call add_dependency(targets(1)%ptr, targets(2)%ptr)
489485
call add_dependency(targets(1)%ptr, targets(3)%ptr)
490486

491-
do i = 1, size(targets)
492-
targets(i)%ptr%output_file = targets(i)%ptr%output_name
493-
end do
494-
495487
! Perform topological sort
496488
do i = 1, size(targets)
497489
call sort_target(targets(i)%ptr)

test/fpm_test/test_installer.f90

Lines changed: 17 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,8 @@ module test_installer
88
use fpm_environment, only : OS_WINDOWS, OS_LINUX
99
use fpm_filesystem, only : join_path
1010
use fpm_installer
11+
use fpm_targets, only: build_target_ptr, add_target, FPM_TARGET_ARCHIVE, &
12+
FPM_TARGET_SHARED
1113
implicit none
1214
private
1315

@@ -116,13 +118,18 @@ subroutine test_install_lib(error)
116118

117119
type(mock_installer_t) :: mock
118120
type(installer_t) :: installer
121+
type(build_target_ptr), allocatable :: targets(:)
119122

120123
call new_installer(installer, prefix="PREFIX", verbosity=0, copy="mock")
121124
mock%installer_t = installer
122125
mock%expected_dir = join_path("PREFIX", "lib")
123126
mock%expected_run = 'mock "name" "'//join_path("PREFIX", "lib")//'"'
127+
128+
call add_target(targets,"name",FPM_TARGET_ARCHIVE,"name")
124129

125-
call mock%install_library("name", error)
130+
call mock%install_library(targets(1)%ptr, error)
131+
132+
deallocate(targets(1)%ptr)
126133

127134
end subroutine test_install_lib
128135

@@ -131,16 +138,16 @@ subroutine test_install_pkgconfig(error)
131138
type(error_t), allocatable, intent(out) :: error
132139

133140
type(mock_installer_t) :: mock
134-
type(installer_t) :: installer
141+
type(installer_t) :: installer
135142

136143
call new_installer(installer, prefix="PREFIX", verbosity=0, copy="mock")
137144
mock%installer_t = installer
138145
mock%os = OS_WINDOWS
139146
mock%expected_dir = "PREFIX\lib\pkgconfig"
140147
mock%expected_run = 'mock "name" "'//mock%expected_dir//'"'
141-
148+
142149
call mock%install("name", "lib/pkgconfig", error)
143-
150+
144151
end subroutine test_install_pkgconfig
145152

146153
subroutine test_install_sitepackages(error)
@@ -184,13 +191,18 @@ subroutine test_install_shared_library_unix(error)
184191
type(mock_installer_t) :: mock
185192
type(installer_t) :: installer
186193
character(len=*), parameter :: libname = "libname.so"
194+
type(build_target_ptr), allocatable :: targets(:)
187195

188196
call new_installer(installer, prefix="PREFIX", verbosity=0, copy="mock")
189197
mock%installer_t = installer
190198
mock%expected_dir = join_path("PREFIX", "lib")
191199
mock%expected_run = 'mock "'//libname//'" "'//mock%expected_dir//'"'
200+
201+
call add_target(targets,"name",FPM_TARGET_SHARED,libname)
192202

193-
call mock%install_library(libname, error)
203+
call mock%install_library(targets(1)%ptr, error)
204+
205+
deallocate(targets(1)%ptr)
194206

195207
end subroutine test_install_shared_library_unix
196208

0 commit comments

Comments
 (0)