aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--fpm/src/fpm.f9017
-rw-r--r--fpm/src/fpm/manifest/build_config.f9018
2 files changed, 24 insertions, 11 deletions
diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90
index af19c65..daa4d98 100644
--- a/fpm/src/fpm.f90
+++ b/fpm/src/fpm.f90
@@ -27,11 +27,12 @@ public :: cmd_build, cmd_install, cmd_run
contains
-recursive subroutine add_libsources_from_package(sources,package_list,package, &
+recursive subroutine add_libsources_from_package(sources,link_libraries,package_list,package, &
package_root,dev_depends,error)
! Discover library sources in a package, recursively including dependencies
!
type(srcfile_t), allocatable, intent(inout), target :: sources(:)
+ type(string_t), allocatable, intent(inout) :: link_libraries(:)
type(string_t), allocatable, intent(inout) :: package_list(:)
type(package_t), intent(in) :: package
character(*), intent(in) :: package_root
@@ -121,7 +122,7 @@ recursive subroutine add_libsources_from_package(sources,package_list,package, &
end if
- call add_libsources_from_package(sources,package_list,dependency, &
+ call add_libsources_from_package(sources,link_libraries,package_list,dependency, &
package_root=dependency_path, &
dev_depends=.false., error=error)
@@ -134,6 +135,9 @@ recursive subroutine add_libsources_from_package(sources,package_list,package, &
dep_name%s = dependency_list(i)%name
package_list = [package_list, dep_name]
+ if (allocated(dependency%build_config%link)) then
+ link_libraries = [link_libraries, dependency%build_config%link]
+ end if
end do
@@ -150,11 +154,14 @@ subroutine build_model(model, settings, package, error)
type(package_t), intent(in) :: package
type(error_t), allocatable, intent(out) :: error
+ integer :: i
type(string_t), allocatable :: package_list(:)
model%package_name = package%name
if (allocated(package%build_config%link)) then
model%link_libraries = package%build_config%link
+ else
+ allocate(model%link_libraries(0))
end if
allocate(package_list(1))
@@ -222,7 +229,7 @@ subroutine build_model(model, settings, package, error)
endif
! Add library sources, including local dependencies
- call add_libsources_from_package(model%sources,package_list,package, &
+ call add_libsources_from_package(model%sources,model%link_libraries,package_list,package, &
package_root='.',dev_depends=.true.,error=error)
if (allocated(error)) then
return
@@ -230,6 +237,10 @@ subroutine build_model(model, settings, package, error)
call targets_from_sources(model,model%sources)
+ do i = 1, size(model%link_libraries)
+ model%link_flags = model%link_flags // " -l" // model%link_libraries(i)%s
+ end do
+
call resolve_module_dependencies(model%targets,error)
end subroutine build_model
diff --git a/fpm/src/fpm/manifest/build_config.f90 b/fpm/src/fpm/manifest/build_config.f90
index cd59ce5..a88fd58 100644
--- a/fpm/src/fpm/manifest/build_config.f90
+++ b/fpm/src/fpm/manifest/build_config.f90
@@ -94,7 +94,7 @@ contains
call fatal_error(error, "Entry in link field cannot be read")
return
end if
- if (allocated(self%link)) then
+ if (allocated(link)) then
allocate(self%link(1))
call move_alloc(link, self%link(1)%s)
end if
@@ -148,7 +148,7 @@ contains
!> Verbosity of the printout
integer, intent(in), optional :: verbosity
- integer :: pr
+ integer :: pr, ilink
character(len=*), parameter :: fmt = '("#", 1x, a, t30, a)'
if (present(verbosity)) then
@@ -160,12 +160,14 @@ contains
if (pr < 1) return
write(unit, fmt) "Build configuration"
- ! if (allocated(self%auto_executables)) then
- write(unit, fmt) " - auto-discovery (apps) ", merge("enabled ", "disabled", self%auto_executables)
- ! end if
- ! if (allocated(self%auto_tests)) then
- write(unit, fmt) " - auto-discovery (tests) ", merge("enabled ", "disabled", self%auto_tests)
- ! end if
+ write(unit, fmt) " - auto-discovery (apps) ", merge("enabled ", "disabled", self%auto_executables)
+ write(unit, fmt) " - auto-discovery (tests) ", merge("enabled ", "disabled", self%auto_tests)
+ if (allocated(self%link)) then
+ write(unit, fmt) " - link against"
+ do ilink = 1, size(self%link)
+ write(unit, fmt) " - " // self%link(ilink)%s
+ end do
+ end if
end subroutine info