Skip to content

Commit 9162137

Browse files
authored
feat: multiple simultaneous library targets (#1168)
2 parents befef9a + b7565cd commit 9162137

File tree

8 files changed

+215
-45
lines changed

8 files changed

+215
-45
lines changed

ci/run_tests.sh

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -344,5 +344,13 @@ pushd static_app_only
344344
test $EXIT_CODE -eq 0
345345
popd
346346

347+
# Test both shared and static library types
348+
pushd both_lib_types
349+
"$fpm" build
350+
"$fpm" install --prefix=.
351+
# Check that exactly 2 libboth_lib_types library files were installed
352+
test $(ls lib/libboth_lib_types* | wc -l) -eq 2
353+
popd
354+
347355
# Cleanup
348356
rm -rf ./*/build
Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
name = "both_lib_types"
2+
library.type=["shared", "static"]
3+
install.library=true
Lines changed: 15 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,15 @@
1+
module both_lib_types
2+
implicit none
3+
private
4+
5+
public :: say_hello
6+
public :: get_number
7+
contains
8+
subroutine say_hello
9+
print *, "Hello from both_lib_types!"
10+
end subroutine say_hello
11+
12+
integer function get_number()
13+
get_number = 42
14+
end function get_number
15+
end module both_lib_types

src/fpm/manifest.f90

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -40,6 +40,7 @@ subroutine default_library(self)
4040

4141
self%source_dir = "src"
4242
self%include_dir = [string_t("include")]
43+
self%lib_type = [string_t("monolithic")]
4344

4445
end subroutine default_library
4546

src/fpm/manifest/library.f90

Lines changed: 70 additions & 28 deletions
Original file line numberDiff line numberDiff line change
@@ -32,8 +32,8 @@ module fpm_manifest_library
3232
!> Alternative build script to be invoked
3333
character(len=:), allocatable :: build_script
3434

35-
!> Shared / Static / Monolithic library
36-
character(:), allocatable :: lib_type
35+
!> Shared / Static / Monolithic library types (can be multiple)
36+
type(string_t), allocatable :: lib_type(:)
3737

3838
contains
3939

@@ -63,10 +63,16 @@ elemental logical function shared(self)
6363
!> Instance of the library configuration
6464
class(library_config_t), intent(in) :: self
6565

66+
integer :: i
67+
68+
shared = .false.
6669
if (allocated(self%lib_type)) then
67-
shared = self%lib_type == "shared"
68-
else
69-
shared = .false.
70+
do i = 1, size(self%lib_type)
71+
if (self%lib_type(i)%s == "shared") then
72+
shared = .true.
73+
return
74+
end if
75+
end do
7076
endif
7177

7278
end function shared
@@ -78,10 +84,16 @@ elemental logical function static(self)
7884
!> Instance of the library configuration
7985
class(library_config_t), intent(in) :: self
8086

87+
integer :: i
88+
89+
static = .false.
8190
if (allocated(self%lib_type)) then
82-
static = self%lib_type == "static"
83-
else
84-
static = .false.
91+
do i = 1, size(self%lib_type)
92+
if (self%lib_type(i)%s == "static") then
93+
static = .true.
94+
return
95+
end if
96+
end do
8597
endif
8698
end function static
8799

@@ -92,7 +104,20 @@ elemental logical function monolithic(self)
92104
!> Instance of the library configuration
93105
class(library_config_t), intent(in) :: self
94106

95-
monolithic = .not.(static(self) .or. shared(self))
107+
integer :: i
108+
109+
if (allocated(self%lib_type)) then
110+
monolithic = .false.
111+
do i = 1, size(self%lib_type)
112+
if (self%lib_type(i)%s == "monolithic") then
113+
monolithic = .true.
114+
return
115+
end if
116+
end do
117+
else
118+
! Default: monolithic
119+
monolithic = .true.
120+
endif
96121
end function monolithic
97122

98123

@@ -108,7 +133,8 @@ subroutine new_library(self, table, error)
108133
!> Error handling
109134
type(error_t), allocatable, intent(out) :: error
110135

111-
integer :: stat
136+
integer :: stat, i
137+
character(len=:), allocatable :: single_type
112138

113139
call check(table, error)
114140
if (allocated(error)) return
@@ -118,36 +144,52 @@ subroutine new_library(self, table, error)
118144
return
119145
end if
120146

121-
if (has_list(table, "type")) then
122-
call syntax_error(error, "Manifest key [library.type] does not allow list input")
123-
return
124-
end if
147+
! library.type can now be either a single value or a list
125148

126149
call get_value(table, "source-dir", self%source_dir, "src")
127150
call get_value(table, "build-script", self%build_script)
128151

129152
call get_list(table, "include-dir", self%include_dir, error)
130153
if (allocated(error)) return
131154

132-
call get_value(table, "type", self%lib_type, "monolithic")
155+
! Parse library type - can be single value or array
156+
if (has_list(table, "type")) then
157+
! Array of types
158+
call get_list(table, "type", self%lib_type, error)
159+
if (allocated(error)) return
160+
else
161+
! Single type - convert to array for consistency
162+
call get_value(table, "type", single_type, "monolithic")
163+
self%lib_type = [string_t(single_type)]
164+
end if
165+
166+
if (.not.allocated(self%lib_type)) then
167+
self%lib_type = [string_t("monolithic")]
168+
end if
133169

134-
select case(self%lib_type)
135-
case("shared","static","monolithic")
136-
! OK
137-
case default
138-
call fatal_error(error,"Value of library.type cannot be '"//self%lib_type &
139-
//"', choose shared/static/monolithic (default)")
170+
! Validate all types in the array
171+
do i = 1, size(self%lib_type)
172+
select case(self%lib_type(i)%s)
173+
case("shared","static","monolithic")
174+
! OK
175+
case default
176+
call fatal_error(error,"Value of library.type cannot be '"//self%lib_type(i)%s &
177+
//"', choose shared/static/monolithic (default)")
178+
return
179+
end select
180+
end do
181+
182+
! Check that monolithic is not specified together with static or shared
183+
if (monolithic(self) .and. (static(self) .or. shared(self))) then
184+
call fatal_error(error,"library.type 'monolithic' cannot be specified together with 'static' or 'shared'")
140185
return
141-
end select
186+
end if
142187

143188
! Set default value of include-dir if not found in manifest
144189
if (.not.allocated(self%include_dir)) then
145190
self%include_dir = [string_t("include")]
146191
end if
147192

148-
if (.not.allocated(self%lib_type)) then
149-
self%lib_type = "monolithic"
150-
end if
151193

152194
end subroutine new_library
153195

@@ -215,7 +257,7 @@ subroutine info(self, unit, verbosity)
215257
write(unit, fmt) "- include directory", string_cat(self%include_dir,",")
216258
end if
217259

218-
write(unit, fmt) "- library type", self%lib_type
260+
write(unit, fmt) "- library type", string_cat(self%lib_type,",")
219261

220262
if (allocated(self%build_script)) then
221263
write(unit, fmt) "- custom build", self%build_script
@@ -272,7 +314,7 @@ subroutine dump_to_toml(self, table, error)
272314
if (allocated(error)) return
273315
call set_list(table, "include-dir", self%include_dir, error)
274316
if (allocated(error)) return
275-
call set_string(table, "type", self%lib_type, error, class_name)
317+
call set_list(table, "type", self%lib_type, error)
276318
if (allocated(error)) return
277319

278320
end subroutine dump_to_toml
@@ -295,7 +337,7 @@ subroutine load_from_toml(self, table, error)
295337
if (allocated(error)) return
296338
call get_list(table, "include-dir", self%include_dir, error)
297339
if (allocated(error)) return
298-
call get_value(table, "type", self%lib_type)
340+
call get_list(table, "type", self%lib_type, error)
299341
if (allocated(error)) return
300342

301343
end subroutine load_from_toml

src/fpm_model.f90

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1117,7 +1117,10 @@ function get_package_libraries_link(model, package_name, prefix, exclude_self, d
11171117
ndep = size(sorted_package_IDs)
11181118
end if
11191119

1120-
package_deps = [(string_t(model%deps%dep(sorted_package_IDs(i))%name),i=1,ndep)]
1120+
allocate(package_deps(ndep))
1121+
do i=1,ndep
1122+
package_deps(i) = string_t(model%deps%dep(sorted_package_IDs(i))%name)
1123+
end do
11211124

11221125
r = model%compiler%enumerate_libraries(prefix, package_deps)
11231126

src/fpm_targets.f90

Lines changed: 64 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -355,12 +355,22 @@ subroutine build_target_list(targets,model,library)
355355
! Individual package libraries are built.
356356
! Create as many targets as the packages in the dependency tree
357357
do j=1,size(model%packages)
358-
359-
lib_name = library_filename(model%packages(j)%name,shared_lib,.false.,get_os_type())
360358

361-
call add_target(targets,package=model%packages(j)%name, &
362-
type=merge(FPM_TARGET_SHARED,FPM_TARGET_ARCHIVE,shared_lib), &
363-
output_name=lib_name)
359+
! Create static library target if requested
360+
if (static_lib) then
361+
lib_name = library_filename(model%packages(j)%name,.false.,.false.,get_os_type())
362+
call add_target(targets,package=model%packages(j)%name, &
363+
type=FPM_TARGET_ARCHIVE, &
364+
output_name=lib_name)
365+
end if
366+
367+
! Create shared library target if requested
368+
if (shared_lib) then
369+
lib_name = library_filename(model%packages(j)%name,.true.,.false.,get_os_type())
370+
call add_target(targets,package=model%packages(j)%name, &
371+
type=FPM_TARGET_SHARED, &
372+
output_name=lib_name)
373+
end if
364374
end do
365375

366376
endif
@@ -388,8 +398,17 @@ subroutine build_target_list(targets,model,library)
388398

389399

390400
if (with_lib .and. sources(i)%unit_scope == FPM_SCOPE_LIB) then
391-
! Archive depends on object
392-
call add_dependency(targets(merge(1,j,monolithic))%ptr, targets(size(targets))%ptr)
401+
! Library targets depend on object
402+
if (monolithic) then
403+
call add_dependency(targets(1)%ptr, targets(size(targets))%ptr)
404+
elseif (static_lib .and. shared_lib) then
405+
! Both types: static at (2*j-1), shared at (2*j)
406+
call add_dependency(targets(2*j-1)%ptr, targets(size(targets))%ptr)
407+
call add_dependency(targets(2*j)%ptr, targets(size(targets))%ptr)
408+
else
409+
! Single type: package j at index j
410+
call add_dependency(targets(j)%ptr, targets(size(targets))%ptr)
411+
end if
393412
end if
394413

395414
case (FPM_UNIT_CPPSOURCE)
@@ -401,8 +420,17 @@ subroutine build_target_list(targets,model,library)
401420
version = model%packages(j)%version)
402421

403422
if (with_lib .and. sources(i)%unit_scope == FPM_SCOPE_LIB) then
404-
! Archive depends on object
405-
call add_dependency(targets(merge(1,j,monolithic))%ptr, targets(size(targets))%ptr)
423+
! Library targets depend on object
424+
if (monolithic) then
425+
call add_dependency(targets(1)%ptr, targets(size(targets))%ptr)
426+
elseif (static_lib .and. shared_lib) then
427+
! Both types: static at (2*j-1), shared at (2*j)
428+
call add_dependency(targets(2*j-1)%ptr, targets(size(targets))%ptr)
429+
call add_dependency(targets(2*j)%ptr, targets(size(targets))%ptr)
430+
else
431+
! Single type: package j at index j
432+
call add_dependency(targets(j)%ptr, targets(size(targets))%ptr)
433+
end if
406434
end if
407435

408436
!> Add stdc++ as a linker flag. If not already there.
@@ -469,9 +497,19 @@ subroutine build_target_list(targets,model,library)
469497

470498
if (with_lib) then
471499
! Executable depends on library file(s)
472-
do k=1,merge(1,size(model%packages),monolithic)
473-
call add_dependency(target, targets(k)%ptr)
474-
end do
500+
if (monolithic) then
501+
call add_dependency(target, targets(1)%ptr)
502+
elseif (static_lib .and. shared_lib) then
503+
! Both types: depend on static libraries (2*k-1) for all packages
504+
do k=1,size(model%packages)
505+
call add_dependency(target, targets(2*k-1)%ptr)
506+
end do
507+
else
508+
! Single type: depend on library for each package
509+
do k=1,size(model%packages)
510+
call add_dependency(target, targets(k)%ptr)
511+
end do
512+
end if
475513
end if
476514

477515
endassociate
@@ -635,7 +673,7 @@ subroutine add_old_targets(targets, add_targets)
635673
! Check for duplicate outputs
636674
do j=1,size(add_targets)
637675
associate(added=>add_targets(j)%ptr)
638-
676+
639677
do i=1,size(targets)
640678

641679
if (targets(i)%ptr%output_name == added%output_name) then
@@ -666,9 +704,18 @@ end subroutine add_old_target
666704
subroutine add_dependency(target, dependency)
667705
type(build_target_t), intent(inout) :: target
668706
type(build_target_t) , intent(in), target :: dependency
669-
707+
708+
integer :: i
709+
710+
! Ensure no duplicate dependencies: it may happen if we loop over two library targets that
711+
! contain the same objects
712+
do i=1,size(target%dependencies)
713+
if (target%dependencies(i)%ptr%output_name == dependency%output_name) return
714+
end do
715+
if (dependency%output_name==target%output_name) return
716+
670717
target%dependencies = [target%dependencies, build_target_ptr(dependency)]
671-
718+
672719
end subroutine add_dependency
673720

674721

@@ -1176,7 +1223,8 @@ subroutine resolve_target_linking(targets, model, library, error)
11761223
has_self_lib = .false.
11771224
find_self: do j=1,size(targets)
11781225
associate(target_loop=>targets(j)%ptr)
1179-
if (any(target_loop%target_type==[FPM_TARGET_SHARED,FPM_TARGET_ARCHIVE]) &
1226+
if ((target_loop%target_type==FPM_TARGET_ARCHIVE .or. &
1227+
(target_loop%target_type==FPM_TARGET_SHARED .and. .not.static)) &
11801228
.and. target_loop%package_name==target%package_name) then
11811229
has_self_lib = .true.
11821230
exit find_self

0 commit comments

Comments
 (0)