Skip to content

Commit

Permalink
Fix unallocated targets array (#954)
Browse files Browse the repository at this point in the history
  • Loading branch information
perazz authored Jul 7, 2023
2 parents 3f511db + 69d3ea7 commit cfd77ce
Showing 1 changed file with 6 additions and 7 deletions.
13 changes: 6 additions & 7 deletions src/fpm_targets.f90
Original file line number Diff line number Diff line change
Expand Up @@ -198,15 +198,14 @@ subroutine build_target_list(targets,model)
character(:), allocatable :: exe_dir, compile_flags
logical :: with_lib

! Initialize targets
allocate(targets(0))

! 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 (n_source < 1) return

with_lib = any([((model%packages(j)%sources(i)%unit_scope == FPM_SCOPE_LIB, &
i=1,size(model%packages(j)%sources)), &
Expand Down Expand Up @@ -826,7 +825,7 @@ subroutine resolve_target_linking(targets, model)
if (.not.allocated(target%compile_flags)) allocate(character(len=0) :: target%compile_flags)

target%compile_flags = target%compile_flags//' '

select case (target%target_type)
case (FPM_TARGET_C_OBJECT)
target%compile_flags = target%compile_flags//model%c_compile_flags
Expand All @@ -835,7 +834,7 @@ subroutine resolve_target_linking(targets, model)
case default
target%compile_flags = target%compile_flags//model%fortran_compile_flags &
& // get_feature_flags(model%compiler, target%features)
end select
end select

!> Get macros as flags.
target%compile_flags = target%compile_flags // get_macros(model%compiler%id, &
Expand Down

0 comments on commit cfd77ce

Please sign in to comment.