Skip to content

Commit fbbfb2c

Browse files
authored
Merge pull request #433 from LKedward/intel-c
Fix to allow compiling C with Intel CC
2 parents 4cbf919 + 079e7da commit fbbfb2c

File tree

5 files changed

+57
-12
lines changed

5 files changed

+57
-12
lines changed

src/fpm.f90

Lines changed: 6 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: run
7+
use fpm_environment, only: run, get_env
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
@@ -63,6 +63,9 @@ subroutine build_model(model, settings, package, error)
6363
model%fortran_compiler = settings%compiler
6464
endif
6565

66+
call get_default_c_compiler(model%fortran_compiler, model%c_compiler)
67+
model%c_compiler = get_env('FPM_C_COMPILER',model%c_compiler)
68+
6669
if (is_unknown_compiler(model%fortran_compiler)) then
6770
write(*, '(*(a:,1x))') &
6871
"<WARN>", "Unknown compiler", model%fortran_compiler, "requested!", &
@@ -183,6 +186,7 @@ subroutine build_model(model, settings, package, error)
183186
if (settings%verbose) then
184187
write(*,*)'<INFO> BUILD_NAME: ',settings%build_name
185188
write(*,*)'<INFO> COMPILER: ',settings%compiler
189+
write(*,*)'<INFO> C COMPILER: ',model%c_compiler
186190
write(*,*)'<INFO> COMPILER OPTIONS: ', model%fortran_compile_flags
187191
write(*,*)'<INFO> INCLUDE DIRECTORIES: [', string_cat(model%include_dirs,','),']'
188192
end if

src/fpm_backend.f90

Lines changed: 6 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -30,8 +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
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
3535

3636
use fpm_strings, only: string_cat
3737

@@ -241,6 +241,10 @@ subroutine build_target(model,target)
241241
call run(model%fortran_compiler//" -c " // target%source%file_name // target%compile_flags &
242242
// " -o " // target%output_file)
243243

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

246250
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: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -117,6 +117,9 @@ module fpm_model
117117
!> Command line name to invoke fortran compiler
118118
character(:), allocatable :: fortran_compiler
119119

120+
!> Command line name to invoke c compiler
121+
character(:), allocatable :: c_compiler
122+
120123
!> Command line flags passed to fortran for compilation
121124
character(:), allocatable :: fortran_compile_flags
122125

src/fpm_targets.f90

Lines changed: 14 additions & 8 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
@@ -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
@@ -448,7 +451,7 @@ subroutine resolve_target_linking(targets, model)
448451

449452
integer :: i
450453
character(:), allocatable :: global_link_flags
451-
character(:), allocatable :: global_compile_flags
454+
character(:), allocatable :: global_include_flags
452455

453456
if (size(targets) == 0) return
454457

@@ -458,17 +461,16 @@ subroutine resolve_target_linking(targets, model)
458461
allocate(character(0) :: global_link_flags)
459462
end if
460463

461-
global_compile_flags = model%fortran_compile_flags
462-
463464
if (allocated(model%link_libraries)) then
464465
if (size(model%link_libraries) > 0) then
465466
global_link_flags = global_link_flags // " -l" // string_cat(model%link_libraries," -l")
466467
end if
467468
end if
468469

470+
allocate(character(0) :: global_include_flags)
469471
if (allocated(model%include_dirs)) then
470472
if (size(model%include_dirs) > 0) then
471-
global_compile_flags = global_compile_flags // &
473+
global_include_flags = global_include_flags // &
472474
& " -I" // string_cat(model%include_dirs," -I")
473475
end if
474476
end if
@@ -477,7 +479,11 @@ subroutine resolve_target_linking(targets, model)
477479

478480
associate(target => targets(i)%ptr)
479481

480-
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
481487

482488
allocate(target%link_objects(0))
483489

0 commit comments

Comments
 (0)