diff options
author | Laurence Kedward <laurence.kedward@bristol.ac.uk> | 2021-04-17 17:18:50 +0100 |
---|---|---|
committer | GitHub <noreply@github.com> | 2021-04-17 17:18:50 +0100 |
commit | fbbfb2c1c316674a83acd666754a3fd18b643d84 (patch) | |
tree | fc38bd0d71a615dac4e847e891771b292cfb1e75 /src | |
parent | 4cbf9194e47991a208cd61b1f3a0a55f0ae16573 (diff) | |
parent | 079e7da06181a6dc9cee6f8f3b1b1c4ebde9e573 (diff) | |
download | fpm-fbbfb2c1c316674a83acd666754a3fd18b643d84.tar.gz fpm-fbbfb2c1c316674a83acd666754a3fd18b643d84.zip |
Merge pull request #433 from LKedward/intel-c
Fix to allow compiling C with Intel CC
Diffstat (limited to 'src')
-rw-r--r-- | src/fpm.f90 | 8 | ||||
-rw-r--r-- | src/fpm_backend.f90 | 8 | ||||
-rw-r--r-- | src/fpm_compiler.f90 | 28 | ||||
-rw-r--r-- | src/fpm_model.f90 | 3 | ||||
-rw-r--r-- | src/fpm_targets.f90 | 22 |
5 files changed, 57 insertions, 12 deletions
diff --git a/src/fpm.f90 b/src/fpm.f90 index a62ffe0..5e86498 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 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,9 @@ subroutine build_model(model, settings, package, error) model%fortran_compiler = settings%compiler endif + 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!", & @@ -183,6 +186,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_backend.f90 b/src/fpm_backend.f90 index 74cef61..8c4cf40 100644 --- a/src/fpm_backend.f90 +++ b/src/fpm_backend.f90 @@ -30,8 +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 @@ -241,6 +241,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 ec366d6..b8a4143 100644 --- a/src/fpm_model.f90 +++ b/src/fpm_model.f90 @@ -117,6 +117,9 @@ type :: fpm_model_t !> Command line name to invoke fortran compiler character(:), allocatable :: fortran_compiler + !> Command line name to invoke c compiler + character(:), allocatable :: c_compiler + !> Command line flags passed to fortran for compilation character(:), allocatable :: fortran_compile_flags 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)) |