Skip to content

Commit c615d57

Browse files
committed
Implement linking against external libraries
1 parent b65a0b3 commit c615d57

File tree

2 files changed

+24
-11
lines changed

2 files changed

+24
-11
lines changed

fpm/src/fpm.f90

Lines changed: 14 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -27,11 +27,12 @@ module fpm
2727
contains
2828

2929

30-
recursive subroutine add_libsources_from_package(sources,package_list,package, &
30+
recursive subroutine add_libsources_from_package(sources,link_libraries,package_list,package, &
3131
package_root,dev_depends,error)
3232
! Discover library sources in a package, recursively including dependencies
3333
!
3434
type(srcfile_t), allocatable, intent(inout), target :: sources(:)
35+
type(string_t), allocatable, intent(inout) :: link_libraries(:)
3536
type(string_t), allocatable, intent(inout) :: package_list(:)
3637
type(package_t), intent(in) :: package
3738
character(*), intent(in) :: package_root
@@ -121,7 +122,7 @@ subroutine add_dependencies(dependency_list)
121122
end if
122123

123124

124-
call add_libsources_from_package(sources,package_list,dependency, &
125+
call add_libsources_from_package(sources,link_libraries,package_list,dependency, &
125126
package_root=dependency_path, &
126127
dev_depends=.false., error=error)
127128

@@ -134,6 +135,9 @@ subroutine add_dependencies(dependency_list)
134135

135136
dep_name%s = dependency_list(i)%name
136137
package_list = [package_list, dep_name]
138+
if (allocated(dependency%build_config%link)) then
139+
link_libraries = [link_libraries, dependency%build_config%link]
140+
end if
137141

138142
end do
139143

@@ -150,11 +154,14 @@ subroutine build_model(model, settings, package, error)
150154
type(package_t), intent(in) :: package
151155
type(error_t), allocatable, intent(out) :: error
152156

157+
integer :: i
153158
type(string_t), allocatable :: package_list(:)
154159

155160
model%package_name = package%name
156161
if (allocated(package%build_config%link)) then
157162
model%link_libraries = package%build_config%link
163+
else
164+
allocate(model%link_libraries(0))
158165
end if
159166

160167
allocate(package_list(1))
@@ -222,14 +229,18 @@ subroutine build_model(model, settings, package, error)
222229
endif
223230

224231
! Add library sources, including local dependencies
225-
call add_libsources_from_package(model%sources,package_list,package, &
232+
call add_libsources_from_package(model%sources,model%link_libraries,package_list,package, &
226233
package_root='.',dev_depends=.true.,error=error)
227234
if (allocated(error)) then
228235
return
229236
end if
230237

231238
call targets_from_sources(model,model%sources)
232239

240+
do i = 1, size(model%link_libraries)
241+
model%link_flags = model%link_flags // " -l" // model%link_libraries(i)%s
242+
end do
243+
233244
call resolve_module_dependencies(model%targets,error)
234245

235246
end subroutine build_model

fpm/src/fpm/manifest/build_config.f90

Lines changed: 10 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -94,7 +94,7 @@ subroutine new_build_config(self, table, error)
9494
call fatal_error(error, "Entry in link field cannot be read")
9595
return
9696
end if
97-
if (allocated(self%link)) then
97+
if (allocated(link)) then
9898
allocate(self%link(1))
9999
call move_alloc(link, self%link(1)%s)
100100
end if
@@ -148,7 +148,7 @@ subroutine info(self, unit, verbosity)
148148
!> Verbosity of the printout
149149
integer, intent(in), optional :: verbosity
150150

151-
integer :: pr
151+
integer :: pr, ilink
152152
character(len=*), parameter :: fmt = '("#", 1x, a, t30, a)'
153153

154154
if (present(verbosity)) then
@@ -160,12 +160,14 @@ subroutine info(self, unit, verbosity)
160160
if (pr < 1) return
161161

162162
write(unit, fmt) "Build configuration"
163-
! if (allocated(self%auto_executables)) then
164-
write(unit, fmt) " - auto-discovery (apps) ", merge("enabled ", "disabled", self%auto_executables)
165-
! end if
166-
! if (allocated(self%auto_tests)) then
167-
write(unit, fmt) " - auto-discovery (tests) ", merge("enabled ", "disabled", self%auto_tests)
168-
! end if
163+
write(unit, fmt) " - auto-discovery (apps) ", merge("enabled ", "disabled", self%auto_executables)
164+
write(unit, fmt) " - auto-discovery (tests) ", merge("enabled ", "disabled", self%auto_tests)
165+
if (allocated(self%link)) then
166+
write(unit, fmt) " - link against"
167+
do ilink = 1, size(self%link)
168+
write(unit, fmt) " - " // self%link(ilink)%s
169+
end do
170+
end if
169171

170172
end subroutine info
171173

0 commit comments

Comments
 (0)