Skip to content

Commit fcc971f

Browse files
committed
Allow external link dependencies with scope limited to targets
- move reader for string list to toml-f proxy - allow link entry in executable and test tables - bump toml-f version to v0.2.1 - add example package linking a single executable against gomp
1 parent cc7fc6e commit fcc971f

File tree

16 files changed

+137
-42
lines changed

16 files changed

+137
-42
lines changed

ci/run_tests.bat

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -132,3 +132,13 @@ if errorlevel 1 exit 1
132132

133133
.\build\gfortran_debug\app\Program_with_module
134134
if errorlevel 1 exit 1
135+
136+
137+
cd ..\link_executable
138+
if errorlevel 1 exit 1
139+
140+
%fpm_path% build
141+
if errorlevel 1 exit 1
142+
143+
.\build\gfortran_debug\app\gomp_test
144+
if errorlevel 1 exit 1

ci/run_tests.sh

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -73,3 +73,7 @@ cd ../program_with_module
7373
cd ../link_external
7474
"${f_fpm_path}" build
7575
./build/gfortran_debug/app/link_external
76+
77+
cd ../link_executable
78+
"${f_fpm_path}" build
79+
./build/gfortran_debug/app/gomp_test

example_packages/README.md

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -17,5 +17,6 @@ the features demonstrated in each package and which versions of fpm are supporte
1717
| program_with_module | App-only; module+program in single source file | Y | Y |
1818
| submodules | Lib-only; submodules (3 levels) | N | Y |
1919
| link_external | Link external library | N | Y |
20+
| link_executable | Link external library to a single executable | N | Y |
2021
| with_c | Compile with `c` source files | N | Y |
2122
| with_makefile | External build command (makefile) | Y | N |
Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
build/*
Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,11 @@
1+
program gomp_example
2+
implicit none
3+
4+
interface
5+
integer function omp_get_num_procs()
6+
end function
7+
end interface
8+
9+
print *, omp_get_num_procs()
10+
11+
end program gomp_example
Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,8 @@
1+
name = "link_executable"
2+
build.auto-executables = false
3+
4+
[[executable]]
5+
name = "gomp_test"
6+
source-dir = "app"
7+
main = "main.f90"
8+
link = ["gomp"]

fpm/fpm.toml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,7 @@ copyright = "2020 fpm contributors"
88
[dependencies]
99
[dependencies.toml-f]
1010
git = "https://github.com/toml-f/toml-f"
11-
tag = "v0.2"
11+
tag = "v0.2.1"
1212

1313
[dependencies.M_CLI2]
1414
git = "https://github.com/urbanjost/M_CLI2.git"

fpm/src/fpm/manifest/build_config.f90

Lines changed: 4 additions & 29 deletions
Original file line numberDiff line numberDiff line change
@@ -11,8 +11,7 @@
1111
module fpm_manifest_build_config
1212
use fpm_error, only : error_t, syntax_error, fatal_error
1313
use fpm_strings, only : string_t
14-
use fpm_toml, only : toml_table, toml_array, toml_key, toml_stat, get_value, &
15-
& len
14+
use fpm_toml, only : toml_table, toml_key, toml_stat, get_value
1615
implicit none
1716
private
1817

@@ -54,9 +53,7 @@ subroutine new_build_config(self, table, error)
5453
!> Error handling
5554
type(error_t), allocatable, intent(out) :: error
5655

57-
integer :: stat, ilink, nlink
58-
type(toml_array), pointer :: children
59-
character(len=:), allocatable :: link
56+
integer :: stat
6057

6158
call check(table, error)
6259
if (allocated(error)) return
@@ -75,30 +72,8 @@ subroutine new_build_config(self, table, error)
7572
return
7673
end if
7774

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(link)) then
98-
allocate(self%link(1))
99-
call move_alloc(link, self%link(1)%s)
100-
end if
101-
end if
75+
call get_value(table, "link", self%link, error)
76+
if (allocated(error)) return
10277

10378
end subroutine new_build_config
10479

fpm/src/fpm/manifest/executable.f90

Lines changed: 9 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -7,11 +7,13 @@
77
!>name = "string"
88
!>source-dir = "path"
99
!>main = "file"
10+
!>link = ["lib"]
1011
!>[executable.dependencies]
1112
!>```
1213
module fpm_manifest_executable
1314
use fpm_manifest_dependency, only : dependency_t, new_dependencies
1415
use fpm_error, only : error_t, syntax_error
16+
use fpm_strings, only : string_t
1517
use fpm_toml, only : toml_table, toml_key, toml_stat, get_value
1618
implicit none
1719
private
@@ -34,6 +36,9 @@ module fpm_manifest_executable
3436
!> Dependency meta data for this executable
3537
type(dependency_t), allocatable :: dependency(:)
3638

39+
!> Libraries to link against
40+
type(string_t), allocatable :: link(:)
41+
3742
contains
3843

3944
!> Print information on this instance
@@ -76,6 +81,9 @@ subroutine new_executable(self, table, error)
7681
if (allocated(error)) return
7782
end if
7883

84+
call get_value(table, "link", self%link, error)
85+
if (allocated(error)) return
86+
7987
end subroutine new_executable
8088

8189

@@ -110,7 +118,7 @@ subroutine check(table, error)
110118
case("name")
111119
name_present = .true.
112120

113-
case("source-dir", "main", "dependencies")
121+
case("source-dir", "main", "dependencies", "link")
114122
continue
115123

116124
end select

fpm/src/fpm/manifest/test.f90

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -11,6 +11,7 @@
1111
!>name = "string"
1212
!>source-dir = "path"
1313
!>main = "file"
14+
!>link = ["lib"]
1415
!>[test.dependencies]
1516
!>```
1617
module fpm_manifest_test
@@ -69,6 +70,9 @@ subroutine new_test(self, table, error)
6970
if (allocated(error)) return
7071
end if
7172

73+
call get_value(table, "link", self%link, error)
74+
if (allocated(error)) return
75+
7276
end subroutine new_test
7377

7478

@@ -103,7 +107,7 @@ subroutine check(table, error)
103107
case("name")
104108
name_present = .true.
105109

106-
case("source-dir", "main", "dependencies")
110+
case("source-dir", "main", "dependencies", "link")
107111
continue
108112

109113
end select

0 commit comments

Comments
 (0)