Skip to content

Commit 4cbf919

Browse files
authored
Merge pull request #438 from LKedward/external-mods
Add: external-modules key to build table for non-fpm modules
2 parents a540c83 + c80169d commit 4cbf919

File tree

6 files changed

+72
-4
lines changed

6 files changed

+72
-4
lines changed

manifest-reference.md

Lines changed: 26 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -33,6 +33,8 @@ Every manifest file consists of the following sections:
3333
Toggle automatic discovery of executables
3434
- [*link*](#link-external-libraries):
3535
Link with external dependencies
36+
- [*external-modules*](#use-system-installed-modules):
37+
Specify modules used that are not within your fpm package
3638
- Target sections:
3739
- [*library*](#library-configuration)
3840
Configuration of the library target
@@ -353,6 +355,30 @@ In this case the order of the libraries matters:
353355
link = ["blas", "lapack"]
354356
```
355357

358+
## Use system-installed modules
359+
360+
To use modules that are not defined within your fpm package or its dependencies,
361+
specify the module name using the *external-modules* key in the *build* table.
362+
363+
> __Important:__ *fpm* cannot automatically locate external module files; it is the responsibility
364+
> of the user to specify the necessary include directories using compiler flags such that
365+
> the compiler can locate external module files during compilation.
366+
367+
*Example:*
368+
369+
```toml
370+
[build]
371+
external-modules = "netcdf"
372+
```
373+
374+
Multiple external modules can be specified as a list.
375+
376+
*Example:*
377+
378+
```toml
379+
[build]
380+
external-modules = ["netcdf", "h5lt"]
381+
```
356382

357383
## Automatic target discovery
358384

src/fpm.f90

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -51,6 +51,7 @@ subroutine build_model(model, settings, package, error)
5151

5252
allocate(model%include_dirs(0))
5353
allocate(model%link_libraries(0))
54+
allocate(model%external_modules(0))
5455

5556
call new_dependency_tree(model%deps, cache=join_path("build", "cache.toml"))
5657
call model%deps%add(package, error)
@@ -171,6 +172,10 @@ subroutine build_model(model, settings, package, error)
171172
if (allocated(dependency%build%link)) then
172173
model%link_libraries = [model%link_libraries, dependency%build%link]
173174
end if
175+
176+
if (allocated(dependency%build%external_modules)) then
177+
model%external_modules = [model%external_modules, dependency%build%external_modules]
178+
end if
174179
end associate
175180
end do
176181
if (allocated(error)) return

src/fpm/manifest/build.f90

Lines changed: 14 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -34,6 +34,9 @@ module fpm_manifest_build
3434
!> Libraries to link against
3535
type(string_t), allocatable :: link(:)
3636

37+
!> External modules to use
38+
type(string_t), allocatable :: external_modules(:)
39+
3740
contains
3841

3942
!> Print information on this instance
@@ -87,6 +90,9 @@ subroutine new_build_config(self, table, error)
8790
call get_value(table, "link", self%link, error)
8891
if (allocated(error)) return
8992

93+
call get_value(table, "external-modules", self%external_modules, error)
94+
if (allocated(error)) return
95+
9096
end subroutine new_build_config
9197

9298

@@ -110,7 +116,7 @@ subroutine check(table, error)
110116
do ikey = 1, size(list)
111117
select case(list(ikey)%key)
112118

113-
case("auto-executables", "auto-examples", "auto-tests", "link")
119+
case("auto-executables", "auto-examples", "auto-tests", "link", "external-modules")
114120
continue
115121

116122
case default
@@ -135,7 +141,7 @@ subroutine info(self, unit, verbosity)
135141
!> Verbosity of the printout
136142
integer, intent(in), optional :: verbosity
137143

138-
integer :: pr, ilink
144+
integer :: pr, ilink, imod
139145
character(len=*), parameter :: fmt = '("#", 1x, a, t30, a)'
140146

141147
if (present(verbosity)) then
@@ -156,6 +162,12 @@ subroutine info(self, unit, verbosity)
156162
write(unit, fmt) " - " // self%link(ilink)%s
157163
end do
158164
end if
165+
if (allocated(self%external_modules)) then
166+
write(unit, fmt) " - external modules"
167+
do imod = 1, size(self%external_modules)
168+
write(unit, fmt) " - " // self%external_modules(imod)%s
169+
end do
170+
end if
159171

160172
end subroutine info
161173

src/fpm_model.f90

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -129,6 +129,9 @@ module fpm_model
129129
!> Native libraries to link against
130130
type(string_t), allocatable :: link_libraries(:)
131131

132+
!> External modules used
133+
type(string_t), allocatable :: external_modules(:)
134+
132135
!> Project dependencies
133136
type(dependency_tree_t) :: deps
134137

@@ -276,6 +279,13 @@ function info_model(model) result(s)
276279
if (i < size(model%link_libraries)) s = s // ", "
277280
end do
278281
s = s // "]"
282+
! type(string_t), allocatable :: external_modules(:)
283+
s = s // ", external_modules=["
284+
do i = 1, size(model%external_modules)
285+
s = s // '"' // model%external_modules(i)%s // '"'
286+
if (i < size(model%external_modules)) s = s // ", "
287+
end do
288+
s = s // "]"
279289
! type(dependency_tree_t) :: deps
280290
! TODO: print `dependency_tree_t` properly, which should become part of the
281291
! model, not imported from another file

src/fpm_targets.f90

Lines changed: 8 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -121,7 +121,7 @@ subroutine targets_from_sources(targets,model,error)
121121

122122
call build_target_list(targets,model)
123123

124-
call resolve_module_dependencies(targets,error)
124+
call resolve_module_dependencies(targets,model%external_modules,error)
125125
if (allocated(error)) return
126126

127127
call resolve_target_linking(targets,model)
@@ -345,8 +345,9 @@ end subroutine add_dependency
345345
!> a source file in the package of the correct scope, then a __fatal error__
346346
!> is returned by the procedure and model construction fails.
347347
!>
348-
subroutine resolve_module_dependencies(targets,error)
348+
subroutine resolve_module_dependencies(targets,external_modules,error)
349349
type(build_target_ptr), intent(inout), target :: targets(:)
350+
type(string_t), intent(in) :: external_modules(:)
350351
type(error_t), allocatable, intent(out) :: error
351352

352353
type(build_target_ptr) :: dep
@@ -364,6 +365,11 @@ subroutine resolve_module_dependencies(targets,error)
364365
cycle
365366
end if
366367

368+
if (targets(i)%ptr%source%modules_used(j)%s .in. external_modules) then
369+
! Dependency satisfied in system-installed module
370+
cycle
371+
end if
372+
367373
if (any(targets(i)%ptr%source%unit_scope == &
368374
[FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST])) then
369375
dep%ptr => &

test/fpm_test/test_module_dependencies.f90

Lines changed: 9 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -67,6 +67,7 @@ subroutine test_library_module_use(error)
6767
type(build_target_ptr), allocatable :: targets(:)
6868

6969
model%output_directory = ''
70+
allocate(model%external_modules(0))
7071
allocate(model%packages(1))
7172
allocate(model%packages(1)%sources(2))
7273

@@ -137,6 +138,7 @@ subroutine test_scope(exe_scope,error)
137138
character(:), allocatable :: scope_str
138139

139140
model%output_directory = ''
141+
allocate(model%external_modules(0))
140142
allocate(model%packages(1))
141143
allocate(model%packages(1)%sources(2))
142144

@@ -196,6 +198,7 @@ subroutine test_program_with_module(error)
196198
type(build_target_ptr), allocatable :: targets(:)
197199

198200
model%output_directory = ''
201+
allocate(model%external_modules(0))
199202
allocate(model%packages(1))
200203
allocate(model%packages(1)%sources(1))
201204

@@ -249,6 +252,7 @@ subroutine test_scope(exe_scope,error)
249252
character(:), allocatable :: scope_str
250253

251254
model%output_directory = ''
255+
allocate(model%external_modules(0))
252256
allocate(model%packages(1))
253257
allocate(model%packages(1)%sources(3))
254258

@@ -308,6 +312,7 @@ subroutine test_missing_library_use(error)
308312
type(build_target_ptr), allocatable :: targets(:)
309313

310314
model%output_directory = ''
315+
allocate(model%external_modules(0))
311316
allocate(model%packages(1))
312317
allocate(model%packages(1)%sources(2))
313318

@@ -335,6 +340,7 @@ subroutine test_missing_program_use(error)
335340
type(build_target_ptr), allocatable :: targets(:)
336341

337342
model%output_directory = ''
343+
allocate(model%external_modules(0))
338344
allocate(model%packages(1))
339345
allocate(model%packages(1)%sources(2))
340346

@@ -361,6 +367,7 @@ subroutine test_invalid_library_use(error)
361367
type(build_target_ptr), allocatable :: targets(:)
362368

363369
model%output_directory = ''
370+
allocate(model%external_modules(0))
364371
allocate(model%packages(1))
365372
allocate(model%packages(1)%sources(2))
366373

@@ -388,6 +395,7 @@ subroutine test_subdirectory_module_use(error)
388395
type(build_target_ptr), allocatable :: targets(:)
389396

390397
model%output_directory = ''
398+
allocate(model%external_modules(0))
391399
allocate(model%packages(1))
392400
allocate(model%packages(1)%sources(2))
393401

@@ -507,6 +515,7 @@ subroutine test_invalid_subdirectory_module_use(error)
507515
type(build_target_ptr), allocatable :: targets(:)
508516

509517
model%output_directory = ''
518+
allocate(model%external_modules(0))
510519
allocate(model%packages(1))
511520
allocate(model%packages(1)%sources(2))
512521

0 commit comments

Comments
 (0)