@@ -174,6 +174,9 @@ module fpm_model
174
174
175
175
contains
176
176
177
+ ! > Check if a package will create a library
178
+ procedure :: has_library = > package_has_library
179
+
177
180
! > Serialization interface
178
181
procedure :: serializable_is_same = > package_is_same
179
182
procedure :: dump_to_toml = > package_dump_to_toml
@@ -1153,6 +1156,7 @@ function get_package_libraries_link(model, package_name, prefix, exclude_self, d
1153
1156
integer :: id,ndep,i
1154
1157
logical :: no_root
1155
1158
integer , allocatable :: sorted_package_IDs(:)
1159
+ logical , allocatable :: empty_package(:)
1156
1160
type (string_t), allocatable :: package_deps(:)
1157
1161
1158
1162
! Get dependency ID of this target
@@ -1184,6 +1188,14 @@ function get_package_libraries_link(model, package_name, prefix, exclude_self, d
1184
1188
ndep = size (sorted_package_IDs)
1185
1189
endif
1186
1190
1191
+ ! Exclusion of package IDs marked "empty" (i.e. they contain no sources)
1192
+ empty_package = .not. model% packages% has_library()
1193
+
1194
+ if (any (empty_package)) then
1195
+ sorted_package_IDs = pack (sorted_package_IDs, .not. empty_package(sorted_package_IDs))
1196
+ ndep = size (sorted_package_IDs)
1197
+ end if
1198
+
1187
1199
package_deps = [(string_t(model% deps% dep(sorted_package_IDs(i))% name),i= 1 ,ndep)]
1188
1200
1189
1201
r = model% compiler% enumerate_libraries(prefix, package_deps)
@@ -1193,4 +1205,17 @@ function get_package_libraries_link(model, package_name, prefix, exclude_self, d
1193
1205
1194
1206
end function get_package_libraries_link
1195
1207
1208
+ ! > Check whether a package has an object library
1209
+ elemental logical function package_has_library(self) result(has_library)
1210
+ class(package_t), intent (in ) :: self
1211
+
1212
+ if (allocated (self% sources)) then
1213
+ has_library = any (self% sources% unit_scope== FPM_SCOPE_LIB)
1214
+ else
1215
+ has_library = .false.
1216
+ end if
1217
+
1218
+ end function package_has_library
1219
+
1220
+
1196
1221
end module fpm_model
0 commit comments