Skip to content

Commit b65a0b3

Browse files
committed
Implement manifest support for link entry
1 parent 581ec60 commit b65a0b3

File tree

4 files changed

+109
-5
lines changed

4 files changed

+109
-5
lines changed

fpm/src/fpm.f90

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -153,6 +153,9 @@ subroutine build_model(model, settings, package, error)
153153
type(string_t), allocatable :: package_list(:)
154154

155155
model%package_name = package%name
156+
if (allocated(package%build_config%link)) then
157+
model%link_libraries = package%build_config%link
158+
end if
156159

157160
allocate(package_list(1))
158161
package_list(1)%s = package%name

fpm/src/fpm/manifest/build_config.f90

Lines changed: 36 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -6,10 +6,13 @@
66
!>[build]
77
!>auto-executables = bool
88
!>auto-tests = bool
9+
!>link = ["lib"]
910
!>```
1011
module fpm_manifest_build_config
1112
use fpm_error, only : error_t, syntax_error, fatal_error
12-
use fpm_toml, only : toml_table, toml_key, toml_stat, get_value
13+
use fpm_strings, only : string_t
14+
use fpm_toml, only : toml_table, toml_array, toml_key, toml_stat, get_value, &
15+
& len
1316
implicit none
1417
private
1518

@@ -25,6 +28,9 @@ module fpm_manifest_build_config
2528
!> Automatic discovery of tests
2629
logical :: auto_tests
2730

31+
!> Libraries to link against
32+
type(string_t), allocatable :: link(:)
33+
2834
contains
2935

3036
!> Print information on this instance
@@ -48,8 +54,9 @@ subroutine new_build_config(self, table, error)
4854
!> Error handling
4955
type(error_t), allocatable, intent(out) :: error
5056

51-
!> Status
52-
integer :: stat
57+
integer :: stat, ilink, nlink
58+
type(toml_array), pointer :: children
59+
character(len=:), allocatable :: link
5360

5461
call check(table, error)
5562
if (allocated(error)) return
@@ -68,6 +75,31 @@ subroutine new_build_config(self, table, error)
6875
return
6976
end if
7077

78+
call get_value(table, "link", children, requested=.false.)
79+
if (associated(children)) then
80+
nlink = len(children)
81+
allocate(self%link(nlink))
82+
do ilink = 1, nlink
83+
call get_value(children, ilink, link, stat=stat)
84+
if (stat /= toml_stat%success) then
85+
call fatal_error(error, "Entry in link field cannot be read")
86+
exit
87+
end if
88+
call move_alloc(link, self%link(ilink)%s)
89+
end do
90+
if (allocated(error)) return
91+
else
92+
call get_value(table, "link", link, stat=stat)
93+
if (stat /= toml_stat%success) then
94+
call fatal_error(error, "Entry in link field cannot be read")
95+
return
96+
end if
97+
if (allocated(self%link)) then
98+
allocate(self%link(1))
99+
call move_alloc(link, self%link(1)%s)
100+
end if
101+
end if
102+
71103
end subroutine new_build_config
72104

73105

@@ -91,7 +123,7 @@ subroutine check(table, error)
91123
do ikey = 1, size(list)
92124
select case(list(ikey)%key)
93125

94-
case("auto-executables", "auto-tests")
126+
case("auto-executables", "auto-tests", "link")
95127
continue
96128

97129
case default

fpm/src/fpm_model.f90

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -87,6 +87,8 @@ module fpm_model
8787
! Command line flags pass for linking
8888
character(:), allocatable :: output_directory
8989
! Base directory for build
90+
type(string_t), allocatable :: link_libraries(:)
91+
! Native libraries to link against
9092
end type fpm_model_t
9193

9294
end module fpm_model

fpm/test/fpm_test/test_manifest.f90

Lines changed: 68 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -51,7 +51,10 @@ subroutine collect_manifest(testsuite)
5151
& new_unittest("test-empty", test_test_empty, should_fail=.true.), &
5252
& new_unittest("test-typeerror", test_test_typeerror, should_fail=.true.), &
5353
& new_unittest("test-noname", test_test_noname, should_fail=.true.), &
54-
& new_unittest("test-wrongkey", test_test_wrongkey, should_fail=.true.)]
54+
& new_unittest("test-wrongkey", test_test_wrongkey, should_fail=.true.), &
55+
& new_unittest("test-link-string", test_link_string), &
56+
& new_unittest("test-link-array", test_link_array), &
57+
& new_unittest("test-link-error", test_invalid_link, should_fail=.true.)]
5558

5659
end subroutine collect_manifest
5760

@@ -850,4 +853,68 @@ subroutine test_test_wrongkey(error)
850853
end subroutine test_test_wrongkey
851854

852855

856+
!> Test link options
857+
subroutine test_link_string(error)
858+
use fpm_manifest_build_config
859+
use fpm_toml, only : set_value, toml_table
860+
861+
!> Error handling
862+
type(error_t), allocatable, intent(out) :: error
863+
864+
type(toml_table) :: table
865+
integer :: stat
866+
type(build_config_t) :: build
867+
868+
table = toml_table()
869+
call set_value(table, "link", "z", stat=stat)
870+
871+
call new_build_config(build, table, error)
872+
873+
end subroutine test_link_string
874+
875+
876+
!> Test link options
877+
subroutine test_link_array(error)
878+
use fpm_manifest_build_config
879+
use fpm_toml, only : add_array, set_value, toml_table, toml_array
880+
881+
!> Error handling
882+
type(error_t), allocatable, intent(out) :: error
883+
884+
type(toml_table) :: table
885+
type(toml_array), pointer :: children
886+
integer :: stat
887+
type(build_config_t) :: build
888+
889+
table = toml_table()
890+
call add_array(table, "link", children, stat=stat)
891+
call set_value(children, 1, "blas", stat=stat)
892+
call set_value(children, 2, "lapack", stat=stat)
893+
894+
call new_build_config(build, table, error)
895+
896+
end subroutine test_link_array
897+
898+
899+
!> Test link options
900+
subroutine test_invalid_link(error)
901+
use fpm_manifest_build_config
902+
use fpm_toml, only : add_table, toml_table
903+
904+
!> Error handling
905+
type(error_t), allocatable, intent(out) :: error
906+
907+
type(toml_table) :: table
908+
type(toml_table), pointer :: child
909+
integer :: stat
910+
type(build_config_t) :: build
911+
912+
table = toml_table()
913+
call add_table(table, "link", child, stat=stat)
914+
915+
call new_build_config(build, table, error)
916+
917+
end subroutine test_invalid_link
918+
919+
853920
end module test_manifest

0 commit comments

Comments
 (0)