Skip to content

Commit a4b2679

Browse files
authored
Merge branch 'main' into custom_module_path
2 parents 42ca4d0 + 9162137 commit a4b2679

File tree

14 files changed

+562
-177
lines changed

14 files changed

+562
-177
lines changed

ci/run_tests.sh

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -358,5 +358,13 @@ test -f ./test_custom_install/lib/libcustom-module-dir.a
358358
rm -rf ./test_custom_install
359359
popd
360360

361+
# Test both shared and static library types
362+
pushd both_lib_types
363+
"$fpm" build
364+
"$fpm" install --prefix=.
365+
# Check that exactly 2 libboth_lib_types library files were installed
366+
test $(ls lib/libboth_lib_types* | wc -l) -eq 2
367+
popd
368+
361369
# Cleanup
362370
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.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,7 @@ module fpm
99
use fpm_dependency, only : new_dependency_tree
1010
use fpm_filesystem, only: is_dir, join_path, list_files, exists, &
1111
basename, filewrite, mkdir, run, os_delete_dir
12-
use fpm_model, only: fpm_model_t, srcfile_t, show_model, fortran_features_t, &
12+
use fpm_model, only: fpm_model_t, srcfile_t, show_model, &
1313
FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, FPM_SCOPE_DEP, &
1414
FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST
1515
use fpm_compiler, only: new_compiler, new_archiver, set_cpp_preprocessor_flags

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

0 commit comments

Comments
 (0)