Skip to content

Commit 01fb0b5

Browse files
committed
export .def and import library on Windows
1 parent c03ceaa commit 01fb0b5

File tree

3 files changed

+60
-18
lines changed

3 files changed

+60
-18
lines changed

src/fpm/cmd/install.f90

Lines changed: 8 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -26,7 +26,7 @@ subroutine cmd_install(settings)
2626
type(package_config_t) :: package
2727
type(error_t), allocatable :: error
2828
type(fpm_model_t) :: model
29-
type(build_target_ptr), allocatable :: targets(:)
29+
type(build_target_ptr), allocatable :: targets(:), libraries(:)
3030
type(installer_t) :: installer
3131
type(string_t), allocatable :: list(:)
3232
logical :: installable
@@ -62,11 +62,11 @@ subroutine cmd_install(settings)
6262
verbosity=merge(2, 1, settings%verbose))
6363

6464
if (allocated(package%library) .and. package%install%library) then
65-
call filter_library_targets(targets, list)
65+
call filter_library_targets(targets, libraries)
6666

67-
if (size(list) > 0) then
68-
do i=1,size(list)
69-
call installer%install_library(list(i)%s, error)
67+
if (size(libraries) > 0) then
68+
do i=1,size(libraries)
69+
call installer%install_library(libraries(i)%ptr, error)
7070
call handle_error(error)
7171
end do
7272

@@ -97,11 +97,12 @@ subroutine install_info(unit, verbose, targets, ntargets)
9797

9898
integer :: ii
9999
type(string_t), allocatable :: install_target(:), temp(:)
100+
type(build_target_ptr), allocatable :: libs(:)
100101

101102
allocate(install_target(0))
102103

103-
call filter_library_targets(targets, temp)
104-
install_target = [install_target, temp]
104+
call filter_library_targets(targets, libs)
105+
install_target = [install_target, (string_t(libs(ii)%ptr%output_file),ii=1,size(libs))]
105106

106107
call filter_executable_targets(targets, FPM_SCOPE_APP, temp)
107108
install_target = [install_target, temp]

src/fpm/installer.f90

Lines changed: 40 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -5,8 +5,9 @@
55
!> to any directory within the prefix.
66
module fpm_installer
77
use, intrinsic :: iso_fortran_env, only : output_unit
8-
use fpm_environment, only : get_os_type, os_is_unix
8+
use fpm_environment, only : get_os_type, os_is_unix, OS_WINDOWS
99
use fpm_error, only : error_t, fatal_error
10+
use fpm_targets, only: build_target_t, FPM_TARGET_ARCHIVE, FPM_TARGET_SHARED, FPM_TARGET_NAME
1011
use fpm_filesystem, only : join_path, mkdir, exists, unix_path, windows_path, get_local_prefix
1112

1213
implicit none
@@ -193,12 +194,46 @@ end subroutine install_executable
193194
subroutine install_library(self, library, error)
194195
!> Instance of the installer
195196
class(installer_t), intent(inout) :: self
196-
!> Path to the library
197-
character(len=*), intent(in) :: library
197+
!> Library target
198+
type(build_target_t), intent(in) :: library
198199
!> Error handling
199200
type(error_t), allocatable, intent(out) :: error
200-
201-
call self%install(library, self%libdir, error)
201+
202+
character(:), allocatable :: def_file, implib_file
203+
204+
select case (library%target_type)
205+
case (FPM_TARGET_ARCHIVE)
206+
call self%install(library%output_file, self%libdir, error)
207+
case (FPM_TARGET_SHARED)
208+
call self%install(library%output_file, self%libdir, error)
209+
210+
! Handle shared library side-files only on Windows
211+
if (self%os==OS_WINDOWS) then
212+
213+
! Install .def if it exists
214+
def_file = join_path(library%output_dir, library%package_name // ".def")
215+
if (exists(def_file)) call self%install(def_file, self%libdir, error)
216+
if (allocated(error)) return
217+
218+
! Try both compiler-dependent import library names
219+
implib_file = join_path(library%output_dir, library%package_name // ".dll.a")
220+
if (exists(implib_file)) then
221+
call self%install(implib_file, self%libdir, error)
222+
if (allocated(error)) return
223+
else
224+
implib_file = join_path(library%output_dir, library%package_name // ".lib")
225+
if (exists(implib_file)) call self%install(implib_file, self%libdir, error)
226+
if (allocated(error)) return
227+
endif
228+
229+
end if
230+
231+
case default
232+
call fatal_error(error,"Installer error: "//library%package_name//" is a "// &
233+
FPM_TARGET_NAME(library%target_type)//", not a library")
234+
return
235+
end select
236+
202237
end subroutine install_library
203238

204239
!> Install a test program in its correct subdirectory

src/fpm_targets.f90

Lines changed: 12 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -1254,23 +1254,29 @@ function get_output_dir(build_prefix, args) result(path)
12541254
path = build_prefix//"_"//build_hash
12551255
end function get_output_dir
12561256

1257-
1257+
!> Returns pointers to all library targets
12581258
subroutine filter_library_targets(targets, list)
12591259
type(build_target_ptr), intent(in) :: targets(:)
1260-
type(string_t), allocatable, intent(out) :: list(:)
1260+
type(build_target_ptr), allocatable, intent(out) :: list(:)
12611261

12621262
integer :: i, n
1263+
1264+
n = 0
1265+
do i = 1, size(targets)
1266+
if (any(targets(i)%ptr%target_type == [FPM_TARGET_ARCHIVE,FPM_TARGET_SHARED])) then
1267+
n = n + 1
1268+
end if
1269+
end do
1270+
1271+
allocate(list(n))
12631272

12641273
n = 0
1265-
call resize(list)
12661274
do i = 1, size(targets)
12671275
if (any(targets(i)%ptr%target_type == [FPM_TARGET_ARCHIVE,FPM_TARGET_SHARED])) then
1268-
if (n >= size(list)) call resize(list)
12691276
n = n + 1
1270-
list(n)%s = targets(i)%ptr%output_file
1277+
list(n)%ptr => targets(i)%ptr
12711278
end if
12721279
end do
1273-
call resize(list, n)
12741280
end subroutine filter_library_targets
12751281

12761282
subroutine filter_executable_targets(targets, scope, list)

0 commit comments

Comments
 (0)