Skip to content

Commit

Permalink
Fix #734: First resolve dependencies, then resolve programs (#737)
Browse files Browse the repository at this point in the history
  • Loading branch information
zoziha authored Sep 7, 2022
1 parent a5d9c70 commit c123a11
Show file tree
Hide file tree
Showing 6 changed files with 102 additions and 56 deletions.
6 changes: 5 additions & 1 deletion ci/run_tests.sh
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
#!/bin/bash
#!/usr/bin/env bash
set -ex

cd "$(dirname $0)/.."
Expand Down Expand Up @@ -138,6 +138,10 @@ pushd preprocess_hello
"$fpm" build
popd

pushd fpm_test_exe_issues
"$fpm" build
popd

pushd cpp_files
"$fpm" test
popd
Expand Down
15 changes: 15 additions & 0 deletions example_packages/fpm_test_exe_issues/fpm.toml
Original file line number Diff line number Diff line change
@@ -0,0 +1,15 @@
# See https://github.com/fortran-lang/fpm/issues/734
name = "fpm-test"

[build]
auto-executables = true
auto-tests = true
auto-examples = true

[install]
library = false

[[executable]]
name = "main"
source-dir = "src"
main = "main.f90"
10 changes: 10 additions & 0 deletions example_packages/fpm_test_exe_issues/src/a/a_mod.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,10 @@
module a_mod
use b_mod, only: hello_world

contains

subroutine a_mod_sub()
call hello_world()
end subroutine

end module
10 changes: 10 additions & 0 deletions example_packages/fpm_test_exe_issues/src/b_mod.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,10 @@
module b_mod
implicit none

contains

subroutine hello_world()
print *, "Hello world!"
end subroutine

end module
6 changes: 6 additions & 0 deletions example_packages/fpm_test_exe_issues/src/main.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
program main
use a_mod
implicit none

call a_mod_sub()
end program
111 changes: 56 additions & 55 deletions src/fpm.f90
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,7 @@ module fpm


use fpm_sources, only: add_executable_sources, add_sources_from_dir
use fpm_targets, only: targets_from_sources, resolve_module_dependencies, &
use fpm_targets, only: targets_from_sources, &
resolve_target_linking, build_target_t, build_target_ptr, &
FPM_TARGET_EXECUTABLE, FPM_TARGET_ARCHIVE
use fpm_manifest, only : get_package_data, package_config_t
Expand Down Expand Up @@ -101,6 +101,61 @@ subroutine build_model(model, settings, package, error)

allocate(model%packages(model%deps%ndep))

do i = 1, model%deps%ndep
associate(dep => model%deps%dep(i))
manifest = join_path(dep%proj_dir, "fpm.toml")

call get_package_data(dependency, manifest, error, &
apply_defaults=.true.)
if (allocated(error)) exit

model%packages(i)%name = dependency%name
call package%version%to_string(version)
model%packages(i)%version = version

if (allocated(dependency%preprocess)) then
do j = 1, size(dependency%preprocess)
if (package%preprocess(j)%name == "cpp") then
model%packages(i)%macros = dependency%preprocess(j)%macros
end if
end do
end if

if (.not.allocated(model%packages(i)%sources)) allocate(model%packages(i)%sources(0))

if (allocated(dependency%library)) then

if (allocated(dependency%library%source_dir)) then
lib_dir = join_path(dep%proj_dir, dependency%library%source_dir)
if (is_dir(lib_dir)) then
call add_sources_from_dir(model%packages(i)%sources, lib_dir, FPM_SCOPE_LIB, &
error=error)
if (allocated(error)) exit
end if
end if

if (allocated(dependency%library%include_dir)) then
do j=1,size(dependency%library%include_dir)
include_dir%s = join_path(dep%proj_dir, dependency%library%include_dir(j)%s)
if (is_dir(include_dir%s)) then
model%include_dirs = [model%include_dirs, include_dir]
end if
end do
end if

end if

if (allocated(dependency%build%link)) then
model%link_libraries = [model%link_libraries, dependency%build%link]
end if

if (allocated(dependency%build%external_modules)) then
model%external_modules = [model%external_modules, dependency%build%external_modules]
end if
end associate
end do
if (allocated(error)) return

! Add sources from executable directories
if (is_dir('app') .and. package%build%auto_executables) then
call add_sources_from_dir(model%packages(1)%sources,'app', FPM_SCOPE_APP, &
Expand Down Expand Up @@ -160,60 +215,6 @@ subroutine build_model(model, settings, package, error)

endif

do i = 1, model%deps%ndep
associate(dep => model%deps%dep(i))
manifest = join_path(dep%proj_dir, "fpm.toml")

call get_package_data(dependency, manifest, error, &
apply_defaults=.true.)
if (allocated(error)) exit

model%packages(i)%name = dependency%name
call package%version%to_string(version)
model%packages(i)%version = version

if (allocated(dependency%preprocess)) then
do j = 1, size(dependency%preprocess)
if (package%preprocess(j)%name == "cpp") then
model%packages(i)%macros = dependency%preprocess(j)%macros
end if
end do
end if

if (.not.allocated(model%packages(i)%sources)) allocate(model%packages(i)%sources(0))

if (allocated(dependency%library)) then

if (allocated(dependency%library%source_dir)) then
lib_dir = join_path(dep%proj_dir, dependency%library%source_dir)
if (is_dir(lib_dir)) then
call add_sources_from_dir(model%packages(i)%sources, lib_dir, FPM_SCOPE_LIB, &
error=error)
if (allocated(error)) exit
end if
end if

if (allocated(dependency%library%include_dir)) then
do j=1,size(dependency%library%include_dir)
include_dir%s = join_path(dep%proj_dir, dependency%library%include_dir(j)%s)
if (is_dir(include_dir%s)) then
model%include_dirs = [model%include_dirs, include_dir]
end if
end do
end if

end if

if (allocated(dependency%build%link)) then
model%link_libraries = [model%link_libraries, dependency%build%link]
end if

if (allocated(dependency%build%external_modules)) then
model%external_modules = [model%external_modules, dependency%build%external_modules]
end if
end associate
end do
if (allocated(error)) return

if (settings%verbose) then
write(*,*)'<INFO> BUILD_NAME: ',model%build_prefix
Expand Down

0 comments on commit c123a11

Please sign in to comment.