@@ -32,8 +32,8 @@ module fpm_manifest_library
32
32
! > Alternative build script to be invoked
33
33
character (len= :), allocatable :: build_script
34
34
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(:)
37
37
38
38
contains
39
39
@@ -63,10 +63,16 @@ elemental logical function shared(self)
63
63
! > Instance of the library configuration
64
64
class(library_config_t), intent (in ) :: self
65
65
66
+ integer :: i
67
+
68
+ shared = .false.
66
69
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
70
76
endif
71
77
72
78
end function shared
@@ -78,10 +84,16 @@ elemental logical function static(self)
78
84
! > Instance of the library configuration
79
85
class(library_config_t), intent (in ) :: self
80
86
87
+ integer :: i
88
+
89
+ static = .false.
81
90
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
85
97
endif
86
98
end function static
87
99
@@ -92,7 +104,20 @@ elemental logical function monolithic(self)
92
104
! > Instance of the library configuration
93
105
class(library_config_t), intent (in ) :: self
94
106
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
96
121
end function monolithic
97
122
98
123
@@ -108,7 +133,8 @@ subroutine new_library(self, table, error)
108
133
! > Error handling
109
134
type (error_t), allocatable , intent (out ) :: error
110
135
111
- integer :: stat
136
+ integer :: stat, i
137
+ character (len= :), allocatable :: single_type
112
138
113
139
call check(table, error)
114
140
if (allocated (error)) return
@@ -118,36 +144,52 @@ subroutine new_library(self, table, error)
118
144
return
119
145
end if
120
146
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
125
148
126
149
call get_value(table, " source-dir" , self% source_dir, " src" )
127
150
call get_value(table, " build-script" , self% build_script)
128
151
129
152
call get_list(table, " include-dir" , self% include_dir, error)
130
153
if (allocated (error)) return
131
154
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
133
169
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'" )
140
185
return
141
- end select
186
+ end if
142
187
143
188
! Set default value of include-dir if not found in manifest
144
189
if (.not. allocated (self% include_dir)) then
145
190
self% include_dir = [string_t(" include" )]
146
191
end if
147
192
148
- if (.not. allocated (self% lib_type)) then
149
- self% lib_type = " monolithic"
150
- end if
151
193
152
194
end subroutine new_library
153
195
@@ -215,7 +257,7 @@ subroutine info(self, unit, verbosity)
215
257
write (unit, fmt) " - include directory" , string_cat(self% include_dir," ," )
216
258
end if
217
259
218
- write (unit, fmt) " - library type" , self% lib_type
260
+ write (unit, fmt) " - library type" , string_cat( self% lib_type, " , " )
219
261
220
262
if (allocated (self% build_script)) then
221
263
write (unit, fmt) " - custom build" , self% build_script
@@ -272,7 +314,7 @@ subroutine dump_to_toml(self, table, error)
272
314
if (allocated (error)) return
273
315
call set_list(table, " include-dir" , self% include_dir, error)
274
316
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)
276
318
if (allocated (error)) return
277
319
278
320
end subroutine dump_to_toml
@@ -295,7 +337,7 @@ subroutine load_from_toml(self, table, error)
295
337
if (allocated (error)) return
296
338
call get_list(table, " include-dir" , self% include_dir, error)
297
339
if (allocated (error)) return
298
- call get_value (table, " type" , self% lib_type)
340
+ call get_list (table, " type" , self% lib_type, error )
299
341
if (allocated (error)) return
300
342
301
343
end subroutine load_from_toml
0 commit comments