aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorBrad Richardson <everythingfunctional@protonmail.com>2021-06-04 11:54:45 -0500
committerGitHub <noreply@github.com>2021-06-04 11:54:45 -0500
commit3c1d638ea9bef4c7e09475dfcc6a94907bad5796 (patch)
tree0bdf3e9b46311dbfc9920e7ce5edff96a96591fd
parent7a8f33721974cb66d44834229aff6dd4e2031eda (diff)
parent6d9004d93460dc15b99051c90d1b58d724b010e6 (diff)
downloadfpm-3c1d638ea9bef4c7e09475dfcc6a94907bad5796.tar.gz
fpm-3c1d638ea9bef4c7e09475dfcc6a94907bad5796.zip
Merge branch 'master' into response-files
-rw-r--r--CONTRIBUTING.md5
-rw-r--r--README.md2
-rw-r--r--manifest-reference.md2
-rw-r--r--src/fpm.f9023
-rw-r--r--src/fpm/cmd/new.f902
-rw-r--r--src/fpm_backend.f9045
-rw-r--r--src/fpm_command_line.f903
-rw-r--r--src/fpm_compiler.f9035
-rw-r--r--src/fpm_environment.f9036
-rw-r--r--src/fpm_filesystem.f9010
-rw-r--r--src/fpm_model.f9010
-rw-r--r--src/fpm_targets.f9022
-rw-r--r--test/new_test/new_test.f906
13 files changed, 137 insertions, 64 deletions
diff --git a/CONTRIBUTING.md b/CONTRIBUTING.md
index 2cc1ffa..a4a2147 100644
--- a/CONTRIBUTING.md
+++ b/CONTRIBUTING.md
@@ -8,8 +8,7 @@ help address your problem, evaluate changes, and guide you through your pull
requests.
By contributing to *fpm*, you certify that you own or are allowed to share the
-content of your contribution under the
-[fpm license](https://github.com/fortran-lang/fpm/blob/master/LICENSE).
+content of your contribution under the [fpm license](LICENSE).
* [Style](#style)
* [Reporting a bug](#reporting-a-bug)
@@ -35,7 +34,7 @@ Before opening a bug report:
1. Check if the issue has already been reported
([issues](https://github.com/fortran-lang/fpm/issues)).
2. Check if it is still an issue or it has been fixed?
- Try to reproduce it with the latest version from the master branch.
+ Try to reproduce it with the latest version from the default branch.
3. Isolate the problem and create a minimal test case.
A good bug report should include all information needed to reproduce the bug.
diff --git a/README.md b/README.md
index 290b586..69ae2ee 100644
--- a/README.md
+++ b/README.md
@@ -60,7 +60,7 @@ or from [miniconda](https://docs.conda.io/en/latest/miniconda.html).
To setup *fpm* within Github actions for automated testing, you can use the [fortran-lang/setup-fpm](https://github.com/marketplace/actions/setup-fpm) action.
-#### Bootstraping on other platforms
+#### Bootstrapping on other platforms
For other platforms and architectures have a look at the [bootstrapping instructions](#bootstrapping-instructions).
diff --git a/manifest-reference.md b/manifest-reference.md
index 77ee2eb..cd79b0b 100644
--- a/manifest-reference.md
+++ b/manifest-reference.md
@@ -429,7 +429,7 @@ To use a specific upstream branch declare the *branch* name with
```toml
[dependencies]
-toml-f = { git = "https://github.com/toml-f/toml-f", branch = "master" }
+toml-f = { git = "https://github.com/toml-f/toml-f", branch = "main" }
```
Alternatively, reference tags by using the *tag* entry
diff --git a/src/fpm.f90 b/src/fpm.f90
index a62ffe0..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: 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
@@ -63,6 +63,10 @@ subroutine build_model(model, settings, package, error)
model%fortran_compiler = settings%compiler
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))') &
"<WARN>", "Unknown compiler", model%fortran_compiler, "requested!", &
@@ -148,7 +152,7 @@ subroutine build_model(model, settings, package, error)
if (.not.allocated(model%packages(i)%sources)) allocate(model%packages(i)%sources(0))
if (allocated(dependency%library)) then
-
+
if (allocated(dependency%library%source_dir)) then
lib_dir = join_path(dep%proj_dir, dependency%library%source_dir)
if (is_dir(lib_dir)) then
@@ -166,7 +170,7 @@ subroutine build_model(model, settings, package, error)
end if
end do
end if
-
+
end if
if (allocated(dependency%build%link)) then
@@ -183,8 +187,9 @@ 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> COMPILER OPTIONS: ', model%fortran_compile_flags
- write(*,*)'<INFO> INCLUDE DIRECTORIES: [', string_cat(model%include_dirs,','),']'
+ 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
! Check for duplicate modules
@@ -195,7 +200,7 @@ subroutine build_model(model, settings, package, error)
end subroutine build_model
! Check for duplicate modules
-subroutine check_modules_for_duplicates(model, duplicates_found)
+subroutine check_modules_for_duplicates(model, duplicates_found)
type(fpm_model_t), intent(in) :: model
integer :: maxsize
integer :: i,j,k,l,m,modi
@@ -375,7 +380,7 @@ subroutine cmd_run(settings,test)
! Check all names are valid
! or no name and found more than one file
- toomany= size(settings%name).eq.0 .and. size(executables).gt.1
+ toomany= size(settings%name).eq.0 .and. size(executables).gt.1
if ( any(.not.found) &
& .or. &
& ( (toomany .and. .not.test) .or. (toomany .and. settings%runner .ne. '') ) &
@@ -425,7 +430,7 @@ subroutine cmd_run(settings,test)
end if
end do
endif
- contains
+ contains
subroutine compact_list_all()
integer, parameter :: LINE_WIDTH = 80
integer :: i, j, nCol
diff --git a/src/fpm/cmd/new.f90 b/src/fpm/cmd/new.f90
index 5149bea..773d7a7 100644
--- a/src/fpm/cmd/new.f90
+++ b/src/fpm/cmd/new.f90
@@ -347,7 +347,7 @@ character(len=:,kind=tfc),allocatable :: littlefile(:)
&' # git repository. ',&
&' # ',&
&' # You can be specific about which version of a dependency you would ',&
- &' # like. By default the latest master master branch is used. You can ',&
+ &' # like. By default the latest default branch is used. You can ',&
&' # optionally specify a branch, a tag or a commit value. ',&
&' # ',&
&' # So here are several alternates for specifying a remote dependency (you ',&
diff --git a/src/fpm_backend.f90 b/src/fpm_backend.f90
index 21e7983..99b6be8 100644
--- a/src/fpm_backend.f90
+++ b/src/fpm_backend.f90
@@ -1,28 +1,28 @@
!># Build backend
-!> Uses a list of `[[build_target_ptr]]` and a valid `[[fpm_model]]` instance
+!> Uses a list of `[[build_target_ptr]]` and a valid `[[fpm_model]]` instance
!> to schedule and execute the compilation and linking of package targets.
-!>
+!>
!> The package build process (`[[build_package]]`) comprises three steps:
!>
!> 1. __Target sorting:__ topological sort of the target dependency graph (`[[sort_target]]`)
!> 2. __Target scheduling:__ group targets into schedule regions based on the sorting (`[[schedule_targets]]`)
!> 3. __Target building:__ generate targets by compilation or linking
-!>
+!>
!> @note If compiled with OpenMP, targets will be build in parallel where possible.
!>
!>### Incremental compilation
-!> The backend process supports *incremental* compilation whereby targets are not
+!> The backend process supports *incremental* compilation whereby targets are not
!> re-compiled if their corresponding dependencies have not been modified.
-!>
+!>
!> - Source-based targets (*i.e.* objects) are not re-compiled if the corresponding source
!> file is unmodified AND all of the target dependencies are not marked for re-compilation
!>
-!> - Link targets (*i.e.* executables and libraries) are not re-compiled if the
+!> - Link targets (*i.e.* executables and libraries) are not re-compiled if the
!> target output file already exists AND all of the target dependencies are not marked for
!> re-compilation
!>
!> Source file modification is determined by a file digest (hash) which is calculated during
-!> the source parsing phase ([[fpm_source_parsing]]) and cached to disk after a target is
+!> the source parsing phase ([[fpm_source_parsing]]) and cached to disk after a target is
!> successfully generated.
!>
module fpm_backend
@@ -30,9 +30,8 @@ module fpm_backend
use fpm_environment, only: run, get_os_type, OS_WINDOWS
use fpm_filesystem, only: dirname, join_path, exists, mkdir, unix_path
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, string_t
implicit none
@@ -58,9 +57,9 @@ subroutine build_package(targets,model)
! Perform depth-first topological sort of targets
do i=1,size(targets)
-
+
call sort_target(targets(i)%ptr)
-
+
end do
! Construct build schedule queue
@@ -78,20 +77,20 @@ subroutine build_package(targets,model)
end do
end do
-
+
end subroutine build_package
-!> Topologically sort a target for scheduling by
+!> Topologically sort a target for scheduling by
!> recursing over its dependencies.
-!>
+!>
!> Checks disk-cached source hashes to determine if objects are
!> up-to-date. Up-to-date sources are tagged as skipped.
!>
-!> On completion, `target` should either be marked as
+!> On completion, `target` should either be marked as
!> sorted (`target%sorted=.true.`) or skipped (`target%skip=.true.`)
!>
-!> If `target` is marked as sorted, `target%schedule` should be an
+!> If `target` is marked as sorted, `target%schedule` should be an
!> integer greater than zero indicating the region for scheduling
!>
recursive subroutine sort_target(target)
@@ -162,7 +161,7 @@ recursive subroutine sort_target(target)
end if
end do
-
+
! Mark flag as processed: either sorted or skipped
target%sorted = .not.target%skip
@@ -241,8 +240,12 @@ 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 &
//" "//target%link_flags// " -o " // target%output_file)
@@ -251,10 +254,10 @@ subroutine build_target(model,target)
select case (get_os_type())
case (OS_WINDOWS)
call write_response_file(target%output_file//".resp" ,target%link_objects)
- call run("ar -rs " // target%output_file // " @" // target%output_file//".resp")
+ call run(model%archiver // target%output_file // " @" // target%output_file//".resp")
case default
- call run("ar -rs " // target%output_file // " " // string_cat(target%link_objects," "))
+ call run(model%archiver // target%output_file // " " // string_cat(target%link_objects," "))
end select
diff --git a/src/fpm_command_line.f90 b/src/fpm_command_line.f90
index 9e9a572..2a2ecf5 100644
--- a/src/fpm_command_line.f90
+++ b/src/fpm_command_line.f90
@@ -25,7 +25,7 @@
module fpm_command_line
use fpm_environment, only : get_os_type, get_env, &
OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_WINDOWS, &
- OS_CYGWIN, OS_SOLARIS, OS_FREEBSD
+ OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD
use M_CLI2, only : set_args, lget, sget, unnamed, remaining, specified
use fpm_strings, only : lower, split, fnv_1a
use fpm_filesystem, only : basename, canon_path, to_fortran_name
@@ -129,6 +129,7 @@ contains
case (OS_CYGWIN); os_type = "OS Type: Cygwin"
case (OS_SOLARIS); os_type = "OS Type: Solaris"
case (OS_FREEBSD); os_type = "OS Type: FreeBSD"
+ case (OS_OPENBSD); os_type = "OS Type: OpenBSD"
case (OS_UNKNOWN); os_type = "OS Type: Unknown"
case default ; os_type = "OS Type: UNKNOWN"
end select
diff --git a/src/fpm_compiler.f90 b/src/fpm_compiler.f90
index a499bb9..389ba94 100644
--- a/src/fpm_compiler.f90
+++ b/src/fpm_compiler.f90
@@ -35,7 +35,8 @@ use fpm_environment, only: &
OS_WINDOWS, &
OS_CYGWIN, &
OS_SOLARIS, &
- OS_FREEBSD
+ OS_FREEBSD, &
+ OS_OPENBSD
implicit none
public :: is_unknown_compiler
public :: get_module_flags
@@ -239,7 +240,6 @@ subroutine get_debug_compile_flags(id, flags)
& -g&
& -assume byterecl&
& -traceback&
- & -coarray=single&
&'
case(id_intel_classic_mac)
flags = '&
@@ -260,7 +260,6 @@ subroutine get_debug_compile_flags(id, flags)
& /Z7&
& /assume:byterecl&
& /traceback&
- & /Qcoarray:single&
&'
case(id_intel_llvm_nix, id_intel_llvm_unknown)
flags = '&
@@ -271,7 +270,6 @@ subroutine get_debug_compile_flags(id, flags)
& -g&
& -assume byterecl&
& -traceback&
- & -coarray=single&
&'
case(id_intel_llvm_windows)
flags = '&
@@ -281,7 +279,6 @@ subroutine get_debug_compile_flags(id, flags)
& /Od&
& /Z7&
& /assume:byterecl&
- & /Qcoarray:single&
&'
case(id_nag)
flags = '&
@@ -332,6 +329,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_environment.f90 b/src/fpm_environment.f90
index 0408ec4..345f6ab 100644
--- a/src/fpm_environment.f90
+++ b/src/fpm_environment.f90
@@ -1,5 +1,5 @@
!> This module contains procedures that interact with the programming environment.
-!!
+!!
!! * [get_os_type] -- Determine the OS type
!! * [get_env] -- return the value of an environment variable
module fpm_environment
@@ -9,6 +9,7 @@ module fpm_environment
public :: os_is_unix
public :: run
public :: get_env
+ public :: get_archiver
integer, parameter, public :: OS_UNKNOWN = 0
integer, parameter, public :: OS_LINUX = 1
@@ -17,12 +18,13 @@ module fpm_environment
integer, parameter, public :: OS_CYGWIN = 4
integer, parameter, public :: OS_SOLARIS = 5
integer, parameter, public :: OS_FREEBSD = 6
+ integer, parameter, public :: OS_OPENBSD = 7
contains
!> Determine the OS type
integer function get_os_type() result(r)
!!
!! Returns one of OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_WINDOWS, OS_CYGWIN,
- !! OS_SOLARIS, OS_FREEBSD.
+ !! OS_SOLARIS, OS_FREEBSD, OS_OPENBSD.
!!
!! At first, the environment variable `OS` is checked, which is usually
!! found on Windows. Then, `OSTYPE` is read in and compared with common
@@ -83,6 +85,12 @@ contains
r = OS_FREEBSD
return
end if
+
+ ! OpenBSD
+ if (index(val, 'OpenBSD') > 0 .or. index(val, 'openbsd') > 0) then
+ r = OS_OPENBSD
+ return
+ end if
end if
! Linux
@@ -110,7 +118,7 @@ contains
end if
end function get_os_type
- !> Compare the output of [[get_os_type]] or the optional
+ !> Compare the output of [[get_os_type]] or the optional
!! passed INTEGER value to the value for OS_WINDOWS
!! and return .TRUE. if they match and .FALSE. otherwise
logical function os_is_unix(os) result(unix)
@@ -150,7 +158,7 @@ contains
function get_env(NAME,DEFAULT) result(VALUE)
implicit none
!> name of environment variable to get the value of
- character(len=*),intent(in) :: NAME
+ character(len=*),intent(in) :: NAME
!> default value to return if the requested value is undefined or blank
character(len=*),intent(in),optional :: DEFAULT
!> the returned value
@@ -182,4 +190,24 @@ contains
if(VALUE.eq.''.and.present(DEFAULT))VALUE=DEFAULT
end function get_env
+ function get_archiver() result(archiver)
+ character(:), allocatable :: archiver
+
+ associate(os_type => get_os_type())
+ if (os_type /= OS_WINDOWS .and. os_type /= OS_UNKNOWN) then
+ archiver = "ar -rs "
+ else
+ block
+ integer :: estat
+
+ call execute_command_line("ar --version", exitstat=estat)
+ if (estat /= 0) then
+ archiver = "lib /OUT:"
+ else
+ archiver = "ar -rs "
+ end if
+ end block
+ end if
+ end associate
+ end function
end module fpm_environment
diff --git a/src/fpm_filesystem.f90 b/src/fpm_filesystem.f90
index 6acd383..28c3b33 100644
--- a/src/fpm_filesystem.f90
+++ b/src/fpm_filesystem.f90
@@ -4,7 +4,7 @@ module fpm_filesystem
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, stdout=>output_unit, stderr=>error_unit
use fpm_environment, only: get_os_type, &
OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_WINDOWS, &
- OS_CYGWIN, OS_SOLARIS, OS_FREEBSD
+ OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD
use fpm_strings, only: f_string, replace, string_t, split
implicit none
private
@@ -192,7 +192,7 @@ logical function is_dir(dir)
select case (get_os_type())
- case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD)
+ case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD)
call execute_command_line("test -d " // dir , exitstat=stat)
case (OS_WINDOWS)
@@ -214,7 +214,7 @@ function join_path(a1,a2,a3,a4,a5) result(path)
character(len=1) :: filesep
select case (get_os_type())
- case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD)
+ case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD)
filesep = '/'
case (OS_WINDOWS)
filesep = '\'
@@ -283,7 +283,7 @@ subroutine mkdir(dir)
if (is_dir(dir)) return
select case (get_os_type())
- case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD)
+ case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD)
call execute_command_line('mkdir -p ' // dir, exitstat=stat)
write (*, '(" + ",2a)') 'mkdir -p ' // dir
@@ -322,7 +322,7 @@ recursive subroutine list_files(dir, files, recurse)
allocate (temp_file, source=get_temp_filename())
select case (get_os_type())
- case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD)
+ case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD)
call execute_command_line('ls -A ' // dir // ' > ' // temp_file, &
exitstat=stat)
case (OS_WINDOWS)
diff --git a/src/fpm_model.f90 b/src/fpm_model.f90
index ec366d6..9746e5f 100644
--- a/src/fpm_model.f90
+++ b/src/fpm_model.f90
@@ -1,6 +1,6 @@
!># The fpm package model
!>
-!> Defines the fpm model data types which encapsulate all information
+!> Defines the fpm model data types which encapsulate all information
!> required to correctly build a package and its dependencies.
!>
!> The process (see `[[build_model(subroutine)]]`) for generating a valid `[[fpm_model]]` involves
@@ -117,6 +117,12 @@ type :: fpm_model_t
!> Command line name to invoke fortran compiler
character(:), allocatable :: fortran_compiler
+ !> 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
@@ -128,7 +134,7 @@ type :: fpm_model_t
!> Native libraries to link against
type(string_t), allocatable :: link_libraries(:)
-
+
!> External modules used
type(string_t), allocatable :: external_modules(:)
diff --git a/src/fpm_targets.f90 b/src/fpm_targets.f90
index 671145d..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
@@ -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
@@ -448,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
@@ -458,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
@@ -477,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/new_test/new_test.f90 b/test/new_test/new_test.f90
index 3c8c453..a6c859b 100644
--- a/test/new_test/new_test.f90
+++ b/test/new_test/new_test.f90
@@ -4,7 +4,7 @@ use fpm_filesystem, only : is_dir, list_files, exists, windows_path, join_path,
dirname
use fpm_strings, only : string_t, operator(.in.)
use fpm_environment, only : run, get_os_type
-use fpm_environment, only : OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_WINDOWS
+use fpm_environment, only : OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD, OS_WINDOWS
implicit none
type(string_t), allocatable :: file_names(:)
integer :: i, j, k
@@ -49,7 +49,7 @@ logical :: IS_OS_WINDOWS
!! o DOS versus POSIX filenames
is_os_windows=.false.
select case (get_os_type())
- case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD)
+ case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD)
call execute_command_line('rm -rf fpm_scratch_*',exitstat=estat,cmdstat=cstat,cmdmsg=message)
path=cmdpath
case (OS_WINDOWS)
@@ -145,7 +145,7 @@ logical :: IS_OS_WINDOWS
! clean up scratch files; might want an option to leave them for inspection
select case (get_os_type())
- case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD)
+ case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD)
call execute_command_line('rm -rf fpm_scratch_*',exitstat=estat,cmdstat=cstat,cmdmsg=message)
case (OS_WINDOWS)
call execute_command_line('rmdir fpm_scratch_* /s /q',exitstat=estat,cmdstat=cstat,cmdmsg=message)