aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--fpm/src/fpm.f901
-rw-r--r--fpm/src/fpm_targets.f9013
2 files changed, 13 insertions, 1 deletions
diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90
index 8557869..5b9c310 100644
--- a/fpm/src/fpm.f90
+++ b/fpm/src/fpm.f90
@@ -141,6 +141,7 @@ subroutine build_model(model, settings, package, error)
if (allocated(error)) exit
model%packages(i)%name = dependency%name
+ if (.not.allocated(model%packages(i)%sources)) allocate(model%packages(i)%sources(0))
if (allocated(dependency%library)) then
diff --git a/fpm/src/fpm_targets.f90 b/fpm/src/fpm_targets.f90
index b6c2e57..6a67e98 100644
--- a/fpm/src/fpm_targets.f90
+++ b/fpm/src/fpm_targets.f90
@@ -156,11 +156,20 @@ subroutine build_target_list(targets,model)
!> The package model from which to construct the target list
type(fpm_model_t), intent(inout), target :: model
- integer :: i, j
+ integer :: i, j, n_source
character(:), allocatable :: xsuffix, exe_dir
type(build_target_t), pointer :: dep
logical :: with_lib
+ ! Check for empty build (e.g. header-only lib)
+ n_source = sum([(size(model%packages(j)%sources), &
+ j=1,size(model%packages))])
+
+ if (n_source < 1) then
+ allocate(targets(0))
+ return
+ end if
+
if (get_os_type() == OS_WINDOWS) then
xsuffix = '.exe'
else
@@ -435,6 +444,8 @@ subroutine resolve_target_linking(targets, model)
character(:), allocatable :: global_link_flags
character(:), allocatable :: global_compile_flags
+ if (size(targets) == 0) return
+
if (targets(1)%ptr%target_type == FPM_TARGET_ARCHIVE) then
global_link_flags = targets(1)%ptr%output_file
else