diff options
author | Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> | 2020-11-08 12:37:33 +0100 |
---|---|---|
committer | Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> | 2020-11-13 09:11:17 +0100 |
commit | b65a0b38bbeba35e6f64a52051e13359375be3a2 (patch) | |
tree | 373cb9e9f9fa70a088d1d2b50e252f8cb10ae469 | |
parent | 581ec60b57d21dba846f0c34648f8968ad1bd7fc (diff) | |
download | fpm-b65a0b38bbeba35e6f64a52051e13359375be3a2.tar.gz fpm-b65a0b38bbeba35e6f64a52051e13359375be3a2.zip |
Implement manifest support for link entry
-rw-r--r-- | fpm/src/fpm.f90 | 3 | ||||
-rw-r--r-- | fpm/src/fpm/manifest/build_config.f90 | 40 | ||||
-rw-r--r-- | fpm/src/fpm_model.f90 | 2 | ||||
-rw-r--r-- | fpm/test/fpm_test/test_manifest.f90 | 69 |
4 files changed, 109 insertions, 5 deletions
diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90 index 47c5213..af19c65 100644 --- a/fpm/src/fpm.f90 +++ b/fpm/src/fpm.f90 @@ -153,6 +153,9 @@ subroutine build_model(model, settings, package, error) 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 + end if allocate(package_list(1)) package_list(1)%s = package%name diff --git a/fpm/src/fpm/manifest/build_config.f90 b/fpm/src/fpm/manifest/build_config.f90 index 0509915..cd59ce5 100644 --- a/fpm/src/fpm/manifest/build_config.f90 +++ b/fpm/src/fpm/manifest/build_config.f90 @@ -6,10 +6,13 @@ !>[build] !>auto-executables = bool !>auto-tests = bool +!>link = ["lib"] !>``` module fpm_manifest_build_config use fpm_error, only : error_t, syntax_error, fatal_error - use fpm_toml, only : toml_table, toml_key, toml_stat, get_value + use fpm_strings, only : string_t + use fpm_toml, only : toml_table, toml_array, toml_key, toml_stat, get_value, & + & len implicit none private @@ -25,6 +28,9 @@ module fpm_manifest_build_config !> Automatic discovery of tests logical :: auto_tests + !> Libraries to link against + type(string_t), allocatable :: link(:) + contains !> Print information on this instance @@ -48,8 +54,9 @@ contains !> Error handling type(error_t), allocatable, intent(out) :: error - !> Status - integer :: stat + integer :: stat, ilink, nlink + type(toml_array), pointer :: children + character(len=:), allocatable :: link call check(table, error) if (allocated(error)) return @@ -68,6 +75,31 @@ contains return end if + call get_value(table, "link", children, requested=.false.) + if (associated(children)) then + nlink = len(children) + allocate(self%link(nlink)) + do ilink = 1, nlink + call get_value(children, ilink, link, stat=stat) + if (stat /= toml_stat%success) then + call fatal_error(error, "Entry in link field cannot be read") + exit + end if + call move_alloc(link, self%link(ilink)%s) + end do + if (allocated(error)) return + else + call get_value(table, "link", link, stat=stat) + if (stat /= toml_stat%success) then + call fatal_error(error, "Entry in link field cannot be read") + return + end if + if (allocated(self%link)) then + allocate(self%link(1)) + call move_alloc(link, self%link(1)%s) + end if + end if + end subroutine new_build_config @@ -91,7 +123,7 @@ contains do ikey = 1, size(list) select case(list(ikey)%key) - case("auto-executables", "auto-tests") + case("auto-executables", "auto-tests", "link") continue case default diff --git a/fpm/src/fpm_model.f90 b/fpm/src/fpm_model.f90 index b8c3220..7643416 100644 --- a/fpm/src/fpm_model.f90 +++ b/fpm/src/fpm_model.f90 @@ -87,6 +87,8 @@ type :: fpm_model_t ! Command line flags pass for linking character(:), allocatable :: output_directory ! Base directory for build + type(string_t), allocatable :: link_libraries(:) + ! Native libraries to link against end type fpm_model_t end module fpm_model diff --git a/fpm/test/fpm_test/test_manifest.f90 b/fpm/test/fpm_test/test_manifest.f90 index 575f255..1116a74 100644 --- a/fpm/test/fpm_test/test_manifest.f90 +++ b/fpm/test/fpm_test/test_manifest.f90 @@ -51,7 +51,10 @@ contains & new_unittest("test-empty", test_test_empty, should_fail=.true.), & & new_unittest("test-typeerror", test_test_typeerror, should_fail=.true.), & & new_unittest("test-noname", test_test_noname, should_fail=.true.), & - & new_unittest("test-wrongkey", test_test_wrongkey, should_fail=.true.)] + & new_unittest("test-wrongkey", test_test_wrongkey, should_fail=.true.), & + & new_unittest("test-link-string", test_link_string), & + & new_unittest("test-link-array", test_link_array), & + & new_unittest("test-link-error", test_invalid_link, should_fail=.true.)] end subroutine collect_manifest @@ -850,4 +853,68 @@ contains end subroutine test_test_wrongkey + !> Test link options + subroutine test_link_string(error) + use fpm_manifest_build_config + use fpm_toml, only : set_value, toml_table + + !> Error handling + type(error_t), allocatable, intent(out) :: error + + type(toml_table) :: table + integer :: stat + type(build_config_t) :: build + + table = toml_table() + call set_value(table, "link", "z", stat=stat) + + call new_build_config(build, table, error) + + end subroutine test_link_string + + + !> Test link options + subroutine test_link_array(error) + use fpm_manifest_build_config + use fpm_toml, only : add_array, set_value, toml_table, toml_array + + !> Error handling + type(error_t), allocatable, intent(out) :: error + + type(toml_table) :: table + type(toml_array), pointer :: children + integer :: stat + type(build_config_t) :: build + + table = toml_table() + call add_array(table, "link", children, stat=stat) + call set_value(children, 1, "blas", stat=stat) + call set_value(children, 2, "lapack", stat=stat) + + call new_build_config(build, table, error) + + end subroutine test_link_array + + + !> Test link options + subroutine test_invalid_link(error) + use fpm_manifest_build_config + use fpm_toml, only : add_table, toml_table + + !> Error handling + type(error_t), allocatable, intent(out) :: error + + type(toml_table) :: table + type(toml_table), pointer :: child + integer :: stat + type(build_config_t) :: build + + table = toml_table() + call add_table(table, "link", child, stat=stat) + + call new_build_config(build, table, error) + + end subroutine test_invalid_link + + end module test_manifest |