Skip to content

Commit a1dbbda

Browse files
Merge branch 'master' into different-archiver-on-windows
2 parents faced23 + fbbfb2c commit a1dbbda

File tree

9 files changed

+129
-18
lines changed

9 files changed

+129
-18
lines changed

README.md

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -101,7 +101,7 @@ This guide explains the process of building *fpm* on a platform for the first ti
101101
To build *fpm* without a prior *fpm* version a single source file version is available
102102
at each release.
103103

104-
To build manually using the single source distribution use
104+
To build manually using the single source distribution, run the following code (from within the current directory)
105105

106106
```
107107
mkdir _tmp

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: 10 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -4,12 +4,12 @@ module fpm
44
use fpm_command_line, only: fpm_build_settings, fpm_new_settings, &
55
fpm_run_settings, fpm_install_settings, fpm_test_settings
66
use fpm_dependency, only : new_dependency_tree
7-
use fpm_environment, only: get_archiver, run
7+
use fpm_environment, only: run, get_env, get_archiver
88
use fpm_filesystem, only: is_dir, join_path, number_of_rows, list_files, exists, basename
99
use fpm_model, only: fpm_model_t, srcfile_t, show_model, &
1010
FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, FPM_SCOPE_DEP, &
1111
FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST
12-
use fpm_compiler, only: get_module_flags, is_unknown_compiler
12+
use fpm_compiler, only: get_module_flags, is_unknown_compiler, get_default_c_compiler
1313

1414

1515
use fpm_sources, only: add_executable_sources, add_sources_from_dir
@@ -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)
@@ -63,6 +64,8 @@ subroutine build_model(model, settings, package, error)
6364
endif
6465

6566
model%archiver = get_archiver()
67+
call get_default_c_compiler(model%fortran_compiler, model%c_compiler)
68+
model%c_compiler = get_env('FPM_C_COMPILER',model%c_compiler)
6669

6770
if (is_unknown_compiler(model%fortran_compiler)) then
6871
write(*, '(*(a:,1x))') &
@@ -173,13 +176,18 @@ subroutine build_model(model, settings, package, error)
173176
if (allocated(dependency%build%link)) then
174177
model%link_libraries = [model%link_libraries, dependency%build%link]
175178
end if
179+
180+
if (allocated(dependency%build%external_modules)) then
181+
model%external_modules = [model%external_modules, dependency%build%external_modules]
182+
end if
176183
end associate
177184
end do
178185
if (allocated(error)) return
179186

180187
if (settings%verbose) then
181188
write(*,*)'<INFO> BUILD_NAME: ',settings%build_name
182189
write(*,*)'<INFO> COMPILER: ',settings%compiler
190+
write(*,*)'<INFO> C COMPILER: ',model%c_compiler
183191
write(*,*)'<INFO> COMPILER OPTIONS: ', model%fortran_compile_flags
184192
write(*,*)'<INFO> INCLUDE DIRECTORIES: [', string_cat(model%include_dirs,','),']'
185193
end if

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_backend.f90

Lines changed: 6 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -30,9 +30,8 @@ module fpm_backend
3030
use fpm_environment, only: run
3131
use fpm_filesystem, only: dirname, join_path, exists, mkdir
3232
use fpm_model, only: fpm_model_t
33-
use fpm_targets, only: build_target_t, build_target_ptr, &
34-
FPM_TARGET_OBJECT, FPM_TARGET_ARCHIVE, FPM_TARGET_EXECUTABLE
35-
33+
use fpm_targets, only: build_target_t, build_target_ptr, FPM_TARGET_OBJECT, &
34+
FPM_TARGET_C_OBJECT, FPM_TARGET_ARCHIVE, FPM_TARGET_EXECUTABLE
3635
use fpm_strings, only: string_cat
3736

3837
implicit none
@@ -241,6 +240,10 @@ subroutine build_target(model,target)
241240
call run(model%fortran_compiler//" -c " // target%source%file_name // target%compile_flags &
242241
// " -o " // target%output_file)
243242

243+
case (FPM_TARGET_C_OBJECT)
244+
call run(model%c_compiler//" -c " // target%source%file_name // target%compile_flags &
245+
// " -o " // target%output_file)
246+
244247
case (FPM_TARGET_EXECUTABLE)
245248

246249
call run(model%fortran_compiler// " " // target%compile_flags &

src/fpm_compiler.f90

Lines changed: 28 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -332,6 +332,34 @@ subroutine get_module_flags(compiler, modpath, flags)
332332

333333
end subroutine get_module_flags
334334

335+
subroutine get_default_c_compiler(f_compiler, c_compiler)
336+
character(len=*), intent(in) :: f_compiler
337+
character(len=:), allocatable, intent(out) :: c_compiler
338+
integer(compiler_enum) :: id
339+
340+
id = get_compiler_id(f_compiler)
341+
342+
select case(id)
343+
344+
case(id_intel_classic_nix, id_intel_classic_mac, id_intel_classic_windows, id_intel_classic_unknown)
345+
c_compiler = 'icc'
346+
347+
case(id_intel_llvm_nix,id_intel_llvm_windows, id_intel_llvm_unknown)
348+
c_compiler = 'icx'
349+
350+
case(id_flang)
351+
c_compiler='clang'
352+
353+
case(id_ibmxl)
354+
c_compiler='xlc'
355+
356+
case default
357+
! Fall-back to using Fortran compiler
358+
c_compiler = f_compiler
359+
end select
360+
361+
end subroutine get_default_c_compiler
362+
335363
function get_compiler_id(compiler) result(id)
336364
character(len=*), intent(in) :: compiler
337365
integer(kind=compiler_enum) :: id

src/fpm_model.f90

Lines changed: 13 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -120,6 +120,9 @@ module fpm_model
120120
!> Command line to invoke for creating static library
121121
character(:), allocatable :: archiver
122122

123+
!> Command line name to invoke c compiler
124+
character(:), allocatable :: c_compiler
125+
123126
!> Command line flags passed to fortran for compilation
124127
character(:), allocatable :: fortran_compile_flags
125128

@@ -132,6 +135,9 @@ module fpm_model
132135
!> Native libraries to link against
133136
type(string_t), allocatable :: link_libraries(:)
134137

138+
!> External modules used
139+
type(string_t), allocatable :: external_modules(:)
140+
135141
!> Project dependencies
136142
type(dependency_tree_t) :: deps
137143

@@ -279,6 +285,13 @@ function info_model(model) result(s)
279285
if (i < size(model%link_libraries)) s = s // ", "
280286
end do
281287
s = s // "]"
288+
! type(string_t), allocatable :: external_modules(:)
289+
s = s // ", external_modules=["
290+
do i = 1, size(model%external_modules)
291+
s = s // '"' // model%external_modules(i)%s // '"'
292+
if (i < size(model%external_modules)) s = s // ", "
293+
end do
294+
s = s // "]"
282295
! type(dependency_tree_t) :: deps
283296
! TODO: print `dependency_tree_t` properly, which should become part of the
284297
! model, not imported from another file

src/fpm_targets.f90

Lines changed: 22 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -35,7 +35,8 @@ module fpm_targets
3535
private
3636

3737
public FPM_TARGET_UNKNOWN, FPM_TARGET_EXECUTABLE, &
38-
FPM_TARGET_ARCHIVE, FPM_TARGET_OBJECT
38+
FPM_TARGET_ARCHIVE, FPM_TARGET_OBJECT, &
39+
FPM_TARGET_C_OBJECT
3940
public build_target_t, build_target_ptr
4041
public targets_from_sources, resolve_module_dependencies
4142
public resolve_target_linking, add_target, add_dependency
@@ -50,7 +51,8 @@ module fpm_targets
5051
integer, parameter :: FPM_TARGET_ARCHIVE = 2
5152
!> Target type is compiled object
5253
integer, parameter :: FPM_TARGET_OBJECT = 3
53-
54+
!> Target type is c compiled object
55+
integer, parameter :: FPM_TARGET_C_OBJECT = 4
5456

5557
!> Wrapper type for constructing arrays of `[[build_target_t]]` pointers
5658
type build_target_ptr
@@ -121,7 +123,7 @@ subroutine targets_from_sources(targets,model,error)
121123

122124
call build_target_list(targets,model)
123125

124-
call resolve_module_dependencies(targets,error)
126+
call resolve_module_dependencies(targets,model%external_modules,error)
125127
if (allocated(error)) return
126128

127129
call resolve_target_linking(targets,model)
@@ -194,7 +196,8 @@ subroutine build_target_list(targets,model)
194196
case (FPM_UNIT_MODULE,FPM_UNIT_SUBMODULE,FPM_UNIT_SUBPROGRAM,FPM_UNIT_CSOURCE)
195197

196198
call add_target(targets,source = sources(i), &
197-
type = FPM_TARGET_OBJECT,&
199+
type = merge(FPM_TARGET_C_OBJECT,FPM_TARGET_OBJECT,&
200+
sources(i)%unit_type==FPM_UNIT_CSOURCE), &
198201
output_file = get_object_name(sources(i)))
199202

200203
if (with_lib .and. sources(i)%unit_scope == FPM_SCOPE_LIB) then
@@ -345,8 +348,9 @@ end subroutine add_dependency
345348
!> a source file in the package of the correct scope, then a __fatal error__
346349
!> is returned by the procedure and model construction fails.
347350
!>
348-
subroutine resolve_module_dependencies(targets,error)
351+
subroutine resolve_module_dependencies(targets,external_modules,error)
349352
type(build_target_ptr), intent(inout), target :: targets(:)
353+
type(string_t), intent(in) :: external_modules(:)
350354
type(error_t), allocatable, intent(out) :: error
351355

352356
type(build_target_ptr) :: dep
@@ -364,6 +368,11 @@ subroutine resolve_module_dependencies(targets,error)
364368
cycle
365369
end if
366370

371+
if (targets(i)%ptr%source%modules_used(j)%s .in. external_modules) then
372+
! Dependency satisfied in system-installed module
373+
cycle
374+
end if
375+
367376
if (any(targets(i)%ptr%source%unit_scope == &
368377
[FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST])) then
369378
dep%ptr => &
@@ -442,7 +451,7 @@ subroutine resolve_target_linking(targets, model)
442451

443452
integer :: i
444453
character(:), allocatable :: global_link_flags
445-
character(:), allocatable :: global_compile_flags
454+
character(:), allocatable :: global_include_flags
446455

447456
if (size(targets) == 0) return
448457

@@ -452,17 +461,16 @@ subroutine resolve_target_linking(targets, model)
452461
allocate(character(0) :: global_link_flags)
453462
end if
454463

455-
global_compile_flags = model%fortran_compile_flags
456-
457464
if (allocated(model%link_libraries)) then
458465
if (size(model%link_libraries) > 0) then
459466
global_link_flags = global_link_flags // " -l" // string_cat(model%link_libraries," -l")
460467
end if
461468
end if
462469

470+
allocate(character(0) :: global_include_flags)
463471
if (allocated(model%include_dirs)) then
464472
if (size(model%include_dirs) > 0) then
465-
global_compile_flags = global_compile_flags // &
473+
global_include_flags = global_include_flags // &
466474
& " -I" // string_cat(model%include_dirs," -I")
467475
end if
468476
end if
@@ -471,7 +479,11 @@ subroutine resolve_target_linking(targets, model)
471479

472480
associate(target => targets(i)%ptr)
473481

474-
target%compile_flags = global_compile_flags
482+
if (target%target_type /= FPM_TARGET_C_OBJECT) then
483+
target%compile_flags = model%fortran_compile_flags//" "//global_include_flags
484+
else
485+
target%compile_flags = global_include_flags
486+
end if
475487

476488
allocate(target%link_objects(0))
477489

0 commit comments

Comments
 (0)