aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorBrad Richardson <everythingfunctional@protonmail.com>2021-04-22 09:20:50 -0500
committerGitHub <noreply@github.com>2021-04-22 09:20:50 -0500
commita1dbbdab1b1c1d3807d9aa970b7943792f33641f (patch)
treeee26e1ff4ccd05ed465463f82b6b3d37ba03e015
parentfaced2359ff7bf1c003aaf3990d006fde1124186 (diff)
parentfbbfb2c1c316674a83acd666754a3fd18b643d84 (diff)
downloadfpm-a1dbbdab1b1c1d3807d9aa970b7943792f33641f.tar.gz
fpm-a1dbbdab1b1c1d3807d9aa970b7943792f33641f.zip
Merge branch 'master' into different-archiver-on-windows
-rw-r--r--README.md2
-rw-r--r--manifest-reference.md26
-rw-r--r--src/fpm.f9012
-rw-r--r--src/fpm/manifest/build.f9016
-rw-r--r--src/fpm_backend.f909
-rw-r--r--src/fpm_compiler.f9028
-rw-r--r--src/fpm_model.f9013
-rw-r--r--src/fpm_targets.f9032
-rw-r--r--test/fpm_test/test_module_dependencies.f909
9 files changed, 129 insertions, 18 deletions
diff --git a/README.md b/README.md
index d4e9002..290b586 100644
--- a/README.md
+++ b/README.md
@@ -101,7 +101,7 @@ This guide explains the process of building *fpm* on a platform for the first ti
To build *fpm* without a prior *fpm* version a single source file version is available
at each release.
-To build manually using the single source distribution use
+To build manually using the single source distribution, run the following code (from within the current directory)
```
mkdir _tmp
diff --git a/manifest-reference.md b/manifest-reference.md
index 1a33dc1..77ee2eb 100644
--- a/manifest-reference.md
+++ b/manifest-reference.md
@@ -33,6 +33,8 @@ Every manifest file consists of the following sections:
Toggle automatic discovery of executables
- [*link*](#link-external-libraries):
Link with external dependencies
+ - [*external-modules*](#use-system-installed-modules):
+ Specify modules used that are not within your fpm package
- Target sections:
- [*library*](#library-configuration)
Configuration of the library target
@@ -353,6 +355,30 @@ In this case the order of the libraries matters:
link = ["blas", "lapack"]
```
+## Use system-installed modules
+
+To use modules that are not defined within your fpm package or its dependencies,
+specify the module name using the *external-modules* key in the *build* table.
+
+> __Important:__ *fpm* cannot automatically locate external module files; it is the responsibility
+> of the user to specify the necessary include directories using compiler flags such that
+> the compiler can locate external module files during compilation.
+
+*Example:*
+
+```toml
+[build]
+external-modules = "netcdf"
+```
+
+Multiple external modules can be specified as a list.
+
+*Example:*
+
+```toml
+[build]
+external-modules = ["netcdf", "h5lt"]
+```
## Automatic target discovery
diff --git a/src/fpm.f90 b/src/fpm.f90
index fa2087d..5854cfb 100644
--- a/src/fpm.f90
+++ b/src/fpm.f90
@@ -4,12 +4,12 @@ use fpm_backend, only: build_package
use fpm_command_line, only: fpm_build_settings, fpm_new_settings, &
fpm_run_settings, fpm_install_settings, fpm_test_settings
use fpm_dependency, only : new_dependency_tree
-use fpm_environment, only: get_archiver, run
+use fpm_environment, only: run, get_env, get_archiver
use fpm_filesystem, only: is_dir, join_path, number_of_rows, list_files, exists, basename
use fpm_model, only: fpm_model_t, srcfile_t, show_model, &
FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, FPM_SCOPE_DEP, &
FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST
-use fpm_compiler, only: get_module_flags, is_unknown_compiler
+use fpm_compiler, only: get_module_flags, is_unknown_compiler, get_default_c_compiler
use fpm_sources, only: add_executable_sources, add_sources_from_dir
@@ -51,6 +51,7 @@ subroutine build_model(model, settings, package, error)
allocate(model%include_dirs(0))
allocate(model%link_libraries(0))
+ allocate(model%external_modules(0))
call new_dependency_tree(model%deps, cache=join_path("build", "cache.toml"))
call model%deps%add(package, error)
@@ -63,6 +64,8 @@ subroutine build_model(model, settings, package, error)
endif
model%archiver = get_archiver()
+ call get_default_c_compiler(model%fortran_compiler, model%c_compiler)
+ model%c_compiler = get_env('FPM_C_COMPILER',model%c_compiler)
if (is_unknown_compiler(model%fortran_compiler)) then
write(*, '(*(a:,1x))') &
@@ -173,6 +176,10 @@ subroutine build_model(model, settings, package, error)
if (allocated(dependency%build%link)) then
model%link_libraries = [model%link_libraries, dependency%build%link]
end if
+
+ if (allocated(dependency%build%external_modules)) then
+ model%external_modules = [model%external_modules, dependency%build%external_modules]
+ end if
end associate
end do
if (allocated(error)) return
@@ -180,6 +187,7 @@ subroutine build_model(model, settings, package, error)
if (settings%verbose) then
write(*,*)'<INFO> BUILD_NAME: ',settings%build_name
write(*,*)'<INFO> COMPILER: ',settings%compiler
+ write(*,*)'<INFO> C COMPILER: ',model%c_compiler
write(*,*)'<INFO> COMPILER OPTIONS: ', model%fortran_compile_flags
write(*,*)'<INFO> INCLUDE DIRECTORIES: [', string_cat(model%include_dirs,','),']'
end if
diff --git a/src/fpm/manifest/build.f90 b/src/fpm/manifest/build.f90
index d96974f..c9b3f44 100644
--- a/src/fpm/manifest/build.f90
+++ b/src/fpm/manifest/build.f90
@@ -34,6 +34,9 @@ module fpm_manifest_build
!> Libraries to link against
type(string_t), allocatable :: link(:)
+ !> External modules to use
+ type(string_t), allocatable :: external_modules(:)
+
contains
!> Print information on this instance
@@ -87,6 +90,9 @@ contains
call get_value(table, "link", self%link, error)
if (allocated(error)) return
+ call get_value(table, "external-modules", self%external_modules, error)
+ if (allocated(error)) return
+
end subroutine new_build_config
@@ -110,7 +116,7 @@ contains
do ikey = 1, size(list)
select case(list(ikey)%key)
- case("auto-executables", "auto-examples", "auto-tests", "link")
+ case("auto-executables", "auto-examples", "auto-tests", "link", "external-modules")
continue
case default
@@ -135,7 +141,7 @@ contains
!> Verbosity of the printout
integer, intent(in), optional :: verbosity
- integer :: pr, ilink
+ integer :: pr, ilink, imod
character(len=*), parameter :: fmt = '("#", 1x, a, t30, a)'
if (present(verbosity)) then
@@ -156,6 +162,12 @@ contains
write(unit, fmt) " - " // self%link(ilink)%s
end do
end if
+ if (allocated(self%external_modules)) then
+ write(unit, fmt) " - external modules"
+ do imod = 1, size(self%external_modules)
+ write(unit, fmt) " - " // self%external_modules(imod)%s
+ end do
+ end if
end subroutine info
diff --git a/src/fpm_backend.f90 b/src/fpm_backend.f90
index f84d2ea..51861b4 100644
--- a/src/fpm_backend.f90
+++ b/src/fpm_backend.f90
@@ -30,9 +30,8 @@ module fpm_backend
use fpm_environment, only: run
use fpm_filesystem, only: dirname, join_path, exists, mkdir
use fpm_model, only: fpm_model_t
-use fpm_targets, only: build_target_t, build_target_ptr, &
- FPM_TARGET_OBJECT, FPM_TARGET_ARCHIVE, FPM_TARGET_EXECUTABLE
-
+use fpm_targets, only: build_target_t, build_target_ptr, FPM_TARGET_OBJECT, &
+ FPM_TARGET_C_OBJECT, FPM_TARGET_ARCHIVE, FPM_TARGET_EXECUTABLE
use fpm_strings, only: string_cat
implicit none
@@ -241,6 +240,10 @@ subroutine build_target(model,target)
call run(model%fortran_compiler//" -c " // target%source%file_name // target%compile_flags &
// " -o " // target%output_file)
+ case (FPM_TARGET_C_OBJECT)
+ call run(model%c_compiler//" -c " // target%source%file_name // target%compile_flags &
+ // " -o " // target%output_file)
+
case (FPM_TARGET_EXECUTABLE)
call run(model%fortran_compiler// " " // target%compile_flags &
diff --git a/src/fpm_compiler.f90 b/src/fpm_compiler.f90
index a499bb9..ca0f4d7 100644
--- a/src/fpm_compiler.f90
+++ b/src/fpm_compiler.f90
@@ -332,6 +332,34 @@ subroutine get_module_flags(compiler, modpath, flags)
end subroutine get_module_flags
+subroutine get_default_c_compiler(f_compiler, c_compiler)
+ character(len=*), intent(in) :: f_compiler
+ character(len=:), allocatable, intent(out) :: c_compiler
+ integer(compiler_enum) :: id
+
+ id = get_compiler_id(f_compiler)
+
+ select case(id)
+
+ case(id_intel_classic_nix, id_intel_classic_mac, id_intel_classic_windows, id_intel_classic_unknown)
+ c_compiler = 'icc'
+
+ case(id_intel_llvm_nix,id_intel_llvm_windows, id_intel_llvm_unknown)
+ c_compiler = 'icx'
+
+ case(id_flang)
+ c_compiler='clang'
+
+ case(id_ibmxl)
+ c_compiler='xlc'
+
+ case default
+ ! Fall-back to using Fortran compiler
+ c_compiler = f_compiler
+ end select
+
+end subroutine get_default_c_compiler
+
function get_compiler_id(compiler) result(id)
character(len=*), intent(in) :: compiler
integer(kind=compiler_enum) :: id
diff --git a/src/fpm_model.f90 b/src/fpm_model.f90
index 84f70d4..9746e5f 100644
--- a/src/fpm_model.f90
+++ b/src/fpm_model.f90
@@ -120,6 +120,9 @@ type :: fpm_model_t
!> Command line to invoke for creating static library
character(:), allocatable :: archiver
+ !> Command line name to invoke c compiler
+ character(:), allocatable :: c_compiler
+
!> Command line flags passed to fortran for compilation
character(:), allocatable :: fortran_compile_flags
@@ -132,6 +135,9 @@ type :: fpm_model_t
!> Native libraries to link against
type(string_t), allocatable :: link_libraries(:)
+ !> External modules used
+ type(string_t), allocatable :: external_modules(:)
+
!> Project dependencies
type(dependency_tree_t) :: deps
@@ -279,6 +285,13 @@ function info_model(model) result(s)
if (i < size(model%link_libraries)) s = s // ", "
end do
s = s // "]"
+ ! type(string_t), allocatable :: external_modules(:)
+ s = s // ", external_modules=["
+ do i = 1, size(model%external_modules)
+ s = s // '"' // model%external_modules(i)%s // '"'
+ if (i < size(model%external_modules)) s = s // ", "
+ end do
+ s = s // "]"
! type(dependency_tree_t) :: deps
! TODO: print `dependency_tree_t` properly, which should become part of the
! model, not imported from another file
diff --git a/src/fpm_targets.f90 b/src/fpm_targets.f90
index 02bb600..c247232 100644
--- a/src/fpm_targets.f90
+++ b/src/fpm_targets.f90
@@ -35,7 +35,8 @@ implicit none
private
public FPM_TARGET_UNKNOWN, FPM_TARGET_EXECUTABLE, &
- FPM_TARGET_ARCHIVE, FPM_TARGET_OBJECT
+ FPM_TARGET_ARCHIVE, FPM_TARGET_OBJECT, &
+ FPM_TARGET_C_OBJECT
public build_target_t, build_target_ptr
public targets_from_sources, resolve_module_dependencies
public resolve_target_linking, add_target, add_dependency
@@ -50,7 +51,8 @@ integer, parameter :: FPM_TARGET_EXECUTABLE = 1
integer, parameter :: FPM_TARGET_ARCHIVE = 2
!> Target type is compiled object
integer, parameter :: FPM_TARGET_OBJECT = 3
-
+!> Target type is c compiled object
+integer, parameter :: FPM_TARGET_C_OBJECT = 4
!> Wrapper type for constructing arrays of `[[build_target_t]]` pointers
type build_target_ptr
@@ -121,7 +123,7 @@ subroutine targets_from_sources(targets,model,error)
call build_target_list(targets,model)
- call resolve_module_dependencies(targets,error)
+ call resolve_module_dependencies(targets,model%external_modules,error)
if (allocated(error)) return
call resolve_target_linking(targets,model)
@@ -194,7 +196,8 @@ subroutine build_target_list(targets,model)
case (FPM_UNIT_MODULE,FPM_UNIT_SUBMODULE,FPM_UNIT_SUBPROGRAM,FPM_UNIT_CSOURCE)
call add_target(targets,source = sources(i), &
- type = FPM_TARGET_OBJECT,&
+ type = merge(FPM_TARGET_C_OBJECT,FPM_TARGET_OBJECT,&
+ sources(i)%unit_type==FPM_UNIT_CSOURCE), &
output_file = get_object_name(sources(i)))
if (with_lib .and. sources(i)%unit_scope == FPM_SCOPE_LIB) then
@@ -345,8 +348,9 @@ end subroutine add_dependency
!> a source file in the package of the correct scope, then a __fatal error__
!> is returned by the procedure and model construction fails.
!>
-subroutine resolve_module_dependencies(targets,error)
+subroutine resolve_module_dependencies(targets,external_modules,error)
type(build_target_ptr), intent(inout), target :: targets(:)
+ type(string_t), intent(in) :: external_modules(:)
type(error_t), allocatable, intent(out) :: error
type(build_target_ptr) :: dep
@@ -364,6 +368,11 @@ subroutine resolve_module_dependencies(targets,error)
cycle
end if
+ if (targets(i)%ptr%source%modules_used(j)%s .in. external_modules) then
+ ! Dependency satisfied in system-installed module
+ cycle
+ end if
+
if (any(targets(i)%ptr%source%unit_scope == &
[FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST])) then
dep%ptr => &
@@ -442,7 +451,7 @@ subroutine resolve_target_linking(targets, model)
integer :: i
character(:), allocatable :: global_link_flags
- character(:), allocatable :: global_compile_flags
+ character(:), allocatable :: global_include_flags
if (size(targets) == 0) return
@@ -452,17 +461,16 @@ subroutine resolve_target_linking(targets, model)
allocate(character(0) :: global_link_flags)
end if
- global_compile_flags = model%fortran_compile_flags
-
if (allocated(model%link_libraries)) then
if (size(model%link_libraries) > 0) then
global_link_flags = global_link_flags // " -l" // string_cat(model%link_libraries," -l")
end if
end if
+ allocate(character(0) :: global_include_flags)
if (allocated(model%include_dirs)) then
if (size(model%include_dirs) > 0) then
- global_compile_flags = global_compile_flags // &
+ global_include_flags = global_include_flags // &
& " -I" // string_cat(model%include_dirs," -I")
end if
end if
@@ -471,7 +479,11 @@ subroutine resolve_target_linking(targets, model)
associate(target => targets(i)%ptr)
- target%compile_flags = global_compile_flags
+ if (target%target_type /= FPM_TARGET_C_OBJECT) then
+ target%compile_flags = model%fortran_compile_flags//" "//global_include_flags
+ else
+ target%compile_flags = global_include_flags
+ end if
allocate(target%link_objects(0))
diff --git a/test/fpm_test/test_module_dependencies.f90 b/test/fpm_test/test_module_dependencies.f90
index f193646..992f227 100644
--- a/test/fpm_test/test_module_dependencies.f90
+++ b/test/fpm_test/test_module_dependencies.f90
@@ -67,6 +67,7 @@ contains
type(build_target_ptr), allocatable :: targets(:)
model%output_directory = ''
+ allocate(model%external_modules(0))
allocate(model%packages(1))
allocate(model%packages(1)%sources(2))
@@ -137,6 +138,7 @@ contains
character(:), allocatable :: scope_str
model%output_directory = ''
+ allocate(model%external_modules(0))
allocate(model%packages(1))
allocate(model%packages(1)%sources(2))
@@ -196,6 +198,7 @@ contains
type(build_target_ptr), allocatable :: targets(:)
model%output_directory = ''
+ allocate(model%external_modules(0))
allocate(model%packages(1))
allocate(model%packages(1)%sources(1))
@@ -249,6 +252,7 @@ contains
character(:), allocatable :: scope_str
model%output_directory = ''
+ allocate(model%external_modules(0))
allocate(model%packages(1))
allocate(model%packages(1)%sources(3))
@@ -308,6 +312,7 @@ contains
type(build_target_ptr), allocatable :: targets(:)
model%output_directory = ''
+ allocate(model%external_modules(0))
allocate(model%packages(1))
allocate(model%packages(1)%sources(2))
@@ -335,6 +340,7 @@ contains
type(build_target_ptr), allocatable :: targets(:)
model%output_directory = ''
+ allocate(model%external_modules(0))
allocate(model%packages(1))
allocate(model%packages(1)%sources(2))
@@ -361,6 +367,7 @@ contains
type(build_target_ptr), allocatable :: targets(:)
model%output_directory = ''
+ allocate(model%external_modules(0))
allocate(model%packages(1))
allocate(model%packages(1)%sources(2))
@@ -388,6 +395,7 @@ contains
type(build_target_ptr), allocatable :: targets(:)
model%output_directory = ''
+ allocate(model%external_modules(0))
allocate(model%packages(1))
allocate(model%packages(1)%sources(2))
@@ -507,6 +515,7 @@ contains
type(build_target_ptr), allocatable :: targets(:)
model%output_directory = ''
+ allocate(model%external_modules(0))
allocate(model%packages(1))
allocate(model%packages(1)%sources(2))