Skip to content

Commit 2570975

Browse files
authored
Merge pull request #733 from arteevraina/cpp-support
feat: added support for C++ files compilation
2 parents f418062 + 294f71b commit 2570975

File tree

15 files changed

+209
-21
lines changed

15 files changed

+209
-21
lines changed

ci/run_tests.sh

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -130,5 +130,9 @@ pushd preprocess_hello
130130
"$fpm" build
131131
popd
132132

133+
pushd cpp_files
134+
"$fpm" test
135+
popd
136+
133137
# Cleanup
134138
rm -rf ./*/build

example_packages/cpp_files/README.md

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,2 @@
1+
# cpp_files
2+
My cool new project!

example_packages/cpp_files/fpm.toml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
name = "cpp_files"
Lines changed: 15 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,15 @@
1+
module cpp_files
2+
use, intrinsic :: ISO_C_Binding
3+
implicit none
4+
private
5+
6+
public :: intvec_maxval
7+
8+
interface
9+
integer function intvec_maxval(array, n) bind(C, name = "intvec_maxval")
10+
import :: c_int, c_size_t
11+
integer(c_int), intent(in) :: array(*)
12+
integer(c_size_t), intent(in), value :: n
13+
end function intvec_maxval
14+
end interface
15+
end module cpp_files
Lines changed: 14 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,14 @@
1+
#include <vector>
2+
#include <algorithm>
3+
4+
extern "C" {
5+
6+
int intvec_maxval(int* array, size_t n){
7+
8+
std::vector<int> vec(array, array + n);
9+
10+
return *(std::max_element(vec.begin(), vec.end()));
11+
12+
}
13+
14+
}
Lines changed: 18 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,18 @@
1+
program check
2+
use iso_c_binding, only: c_size_t
3+
use cpp_files
4+
implicit none
5+
6+
integer :: i, max_element
7+
integer, parameter :: array(*) = [(i,i=-50,10)]
8+
9+
max_element = intvec_maxval(array,size(array,1,c_size_t))
10+
11+
if (max_element == maxval(array)) then
12+
write(*,*) ' PASSED: Max element is ',max_element
13+
else
14+
write(*,*) ' (!) FAILED: Incorrect max element returned'
15+
stop 1
16+
end if
17+
18+
end program check

src/fpm.f90

Lines changed: 6 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -43,7 +43,7 @@ subroutine build_model(model, settings, package, error)
4343

4444
integer :: i, j
4545
type(package_config_t) :: dependency
46-
character(len=:), allocatable :: manifest, lib_dir, flags, cflags, ldflags
46+
character(len=:), allocatable :: manifest, lib_dir, flags, cflags, cxxflags, ldflags
4747
character(len=:), allocatable :: version
4848

4949
logical :: duplicates_found = .false.
@@ -65,7 +65,7 @@ subroutine build_model(model, settings, package, error)
6565
end if
6666

6767
call new_compiler(model%compiler, settings%compiler, settings%c_compiler, &
68-
& echo=settings%verbose, verbose=settings%verbose)
68+
& settings%cxx_compiler, echo=settings%verbose, verbose=settings%verbose)
6969
call new_archiver(model%archiver, settings%archiver, &
7070
& echo=settings%verbose, verbose=settings%verbose)
7171

@@ -82,6 +82,7 @@ subroutine build_model(model, settings, package, error)
8282
call set_preprocessor_flags(model%compiler%id, flags, package)
8383

8484
cflags = trim(settings%cflag)
85+
cxxflags = trim(settings%cxxflag)
8586
ldflags = trim(settings%ldflag)
8687

8788
if (model%compiler%is_unknown()) then
@@ -93,6 +94,7 @@ subroutine build_model(model, settings, package, error)
9394

9495
model%fortran_compile_flags = flags
9596
model%c_compile_flags = cflags
97+
model%cxx_compile_flags = cxxflags
9698
model%link_flags = ldflags
9799

98100
model%include_tests = settings%build_tests
@@ -217,8 +219,10 @@ subroutine build_model(model, settings, package, error)
217219
write(*,*)'<INFO> BUILD_NAME: ',model%build_prefix
218220
write(*,*)'<INFO> COMPILER: ',model%compiler%fc
219221
write(*,*)'<INFO> C COMPILER: ',model%compiler%cc
222+
write(*,*)'<INFO> CXX COMPILER: ',model%compiler%cxx
220223
write(*,*)'<INFO> COMPILER OPTIONS: ', model%fortran_compile_flags
221224
write(*,*)'<INFO> C COMPILER OPTIONS: ', model%c_compile_flags
225+
write(*,*)'<INFO> CXX COMPILER OPTIONS: ', model%cxx_compile_flags
222226
write(*,*)'<INFO> LINKER OPTIONS: ', model%link_flags
223227
write(*,*)'<INFO> INCLUDE DIRECTORIES: [', string_cat(model%include_dirs,','),']'
224228
end if

src/fpm_backend.F90

Lines changed: 6 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -33,7 +33,8 @@ module fpm_backend
3333
use fpm_model, only: fpm_model_t
3434
use fpm_strings, only: string_t, operator(.in.)
3535
use fpm_targets, only: build_target_t, build_target_ptr, FPM_TARGET_OBJECT, &
36-
FPM_TARGET_C_OBJECT, FPM_TARGET_ARCHIVE, FPM_TARGET_EXECUTABLE
36+
FPM_TARGET_C_OBJECT, FPM_TARGET_ARCHIVE, FPM_TARGET_EXECUTABLE, &
37+
FPM_TARGET_CPP_OBJECT
3738
use fpm_backend_output
3839
implicit none
3940

@@ -323,6 +324,10 @@ subroutine build_target(model,target,verbose,stat)
323324
call model%compiler%compile_c(target%source%file_name, target%output_file, &
324325
& target%compile_flags, target%output_log_file, stat)
325326

327+
case (FPM_TARGET_CPP_OBJECT)
328+
call model%compiler%compile_cpp(target%source%file_name, target%output_file, &
329+
& target%compile_flags, target%output_log_file, stat)
330+
326331
case (FPM_TARGET_EXECUTABLE)
327332
call model%compiler%link(target%output_file, &
328333
& target%compile_flags//" "//target%link_flags, target%output_log_file, stat)

src/fpm_command_line.f90

Lines changed: 22 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -74,10 +74,12 @@ module fpm_command_line
7474
logical :: prune=.true.
7575
character(len=:),allocatable :: compiler
7676
character(len=:),allocatable :: c_compiler
77+
character(len=:),allocatable :: cxx_compiler
7778
character(len=:),allocatable :: archiver
7879
character(len=:),allocatable :: profile
7980
character(len=:),allocatable :: flag
8081
character(len=:),allocatable :: cflag
82+
character(len=:),allocatable :: cxxflag
8183
character(len=:),allocatable :: ldflag
8284
end type
8385

@@ -128,7 +130,7 @@ module fpm_command_line
128130
& ' ', 'fpm', 'new', 'build', 'run', 'clean', &
129131
& 'test', 'runner', 'install', 'update', 'list', 'help', 'version' ]
130132

131-
character(len=:), allocatable :: val_runner, val_compiler, val_flag, val_cflag, val_ldflag, &
133+
character(len=:), allocatable :: val_runner, val_compiler, val_flag, val_cflag, val_cxxflag, val_ldflag, &
132134
val_profile
133135

134136
! '12345678901234567890123456789012345678901234567890123456789012345678901234567890',&
@@ -197,11 +199,12 @@ subroutine get_command_line_settings(cmd_settings)
197199
logical :: unix
198200
type(fpm_install_settings), allocatable :: install_settings
199201
character(len=:), allocatable :: common_args, compiler_args, run_args, working_dir, &
200-
& c_compiler, archiver
202+
& c_compiler, cxx_compiler, archiver
201203

202204
character(len=*), parameter :: fc_env = "FC", cc_env = "CC", ar_env = "AR", &
203-
& fflags_env = "FFLAGS", cflags_env = "CFLAGS", ldflags_env = "LDFLAGS", &
204-
& fc_default = "gfortran", cc_default = " ", ar_default = " ", flags_default = " "
205+
& fflags_env = "FFLAGS", cflags_env = "CFLAGS", cxxflags_env = "CXXFLAGS", ldflags_env = "LDFLAGS", &
206+
& fc_default = "gfortran", cc_default = " ", ar_default = " ", flags_default = " ", &
207+
& cxx_env = "CXX", cxx_default = " "
205208
type(error_t), allocatable :: error
206209

207210
call set_help()
@@ -245,9 +248,11 @@ subroutine get_command_line_settings(cmd_settings)
245248
' --no-prune F' // &
246249
' --compiler "'//get_fpm_env(fc_env, fc_default)//'"' // &
247250
' --c-compiler "'//get_fpm_env(cc_env, cc_default)//'"' // &
251+
' --cxx-compiler "'//get_fpm_env(cxx_env, cxx_default)//'"' // &
248252
' --archiver "'//get_fpm_env(ar_env, ar_default)//'"' // &
249253
' --flag:: "'//get_fpm_env(fflags_env, flags_default)//'"' // &
250254
' --c-flag:: "'//get_fpm_env(cflags_env, flags_default)//'"' // &
255+
' --cxx-flag:: "'//get_fpm_env(cxxflags_env, flags_default)//'"' // &
251256
' --link-flag:: "'//get_fpm_env(ldflags_env, flags_default)//'"'
252257

253258
! now set subcommand-specific help text and process commandline
@@ -286,6 +291,7 @@ subroutine get_command_line_settings(cmd_settings)
286291
enddo
287292

288293
c_compiler = sget('c-compiler')
294+
cxx_compiler = sget('cxx-compiler')
289295
archiver = sget('archiver')
290296
allocate(fpm_run_settings :: cmd_settings)
291297
val_runner=sget('runner')
@@ -296,9 +302,11 @@ subroutine get_command_line_settings(cmd_settings)
296302
& prune=.not.lget('no-prune'), &
297303
& compiler=val_compiler, &
298304
& c_compiler=c_compiler, &
305+
& cxx_compiler=cxx_compiler, &
299306
& archiver=archiver, &
300307
& flag=val_flag, &
301308
& cflag=val_cflag, &
309+
& cxxflag=val_cxxflag, &
302310
& ldflag=val_ldflag, &
303311
& example=lget('example'), &
304312
& list=lget('list'),&
@@ -317,16 +325,19 @@ subroutine get_command_line_settings(cmd_settings)
317325
call check_build_vals()
318326

319327
c_compiler = sget('c-compiler')
328+
cxx_compiler = sget('cxx-compiler')
320329
archiver = sget('archiver')
321330
allocate( fpm_build_settings :: cmd_settings )
322331
cmd_settings=fpm_build_settings( &
323332
& profile=val_profile,&
324333
& prune=.not.lget('no-prune'), &
325334
& compiler=val_compiler, &
326335
& c_compiler=c_compiler, &
336+
& cxx_compiler=cxx_compiler, &
327337
& archiver=archiver, &
328338
& flag=val_flag, &
329339
& cflag=val_cflag, &
340+
& cxxflag=val_cxxflag, &
330341
& ldflag=val_ldflag, &
331342
& list=lget('list'),&
332343
& show_model=lget('show-model'),&
@@ -470,6 +481,7 @@ subroutine get_command_line_settings(cmd_settings)
470481
call check_build_vals()
471482

472483
c_compiler = sget('c-compiler')
484+
cxx_compiler = sget('cxx-compiler')
473485
archiver = sget('archiver')
474486
allocate(install_settings)
475487
install_settings = fpm_install_settings(&
@@ -478,9 +490,11 @@ subroutine get_command_line_settings(cmd_settings)
478490
prune=.not.lget('no-prune'), &
479491
compiler=val_compiler, &
480492
c_compiler=c_compiler, &
493+
cxx_compiler=cxx_compiler, &
481494
archiver=archiver, &
482495
flag=val_flag, &
483496
cflag=val_cflag, &
497+
cxxflag=val_cxxflag, &
484498
ldflag=val_ldflag, &
485499
no_rebuild=lget('no-rebuild'), &
486500
verbose=lget('verbose'))
@@ -523,6 +537,7 @@ subroutine get_command_line_settings(cmd_settings)
523537
enddo
524538

525539
c_compiler = sget('c-compiler')
540+
cxx_compiler = sget('cxx-compiler')
526541
archiver = sget('archiver')
527542
allocate(fpm_test_settings :: cmd_settings)
528543
val_runner=sget('runner')
@@ -533,9 +548,11 @@ subroutine get_command_line_settings(cmd_settings)
533548
& prune=.not.lget('no-prune'), &
534549
& compiler=val_compiler, &
535550
& c_compiler=c_compiler, &
551+
& cxx_compiler=cxx_compiler, &
536552
& archiver=archiver, &
537553
& flag=val_flag, &
538554
& cflag=val_cflag, &
555+
& cxxflag=val_cxxflag, &
539556
& ldflag=val_ldflag, &
540557
& example=.false., &
541558
& list=lget('list'), &
@@ -616,6 +633,7 @@ subroutine check_build_vals()
616633

617634
val_flag = " " // sget('flag')
618635
val_cflag = " " // sget('c-flag')
636+
val_cxxflag = " "// sget('cxx-flag')
619637
val_ldflag = " " // sget('link-flag')
620638
val_profile = sget('profile')
621639

src/fpm_compiler.f90

Lines changed: 66 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -81,6 +81,8 @@ module fpm_compiler
8181
character(len=:), allocatable :: fc
8282
!> Path to the C compiler
8383
character(len=:), allocatable :: cc
84+
!> Path to the C++ compiler
85+
character(len=:), allocatable :: cxx
8486
!> Print all commands
8587
logical :: echo = .true.
8688
!> Verbose output of command
@@ -96,6 +98,8 @@ module fpm_compiler
9698
procedure :: compile_fortran
9799
!> Compile a C object
98100
procedure :: compile_c
101+
!> Compile a CPP object
102+
procedure :: compile_cpp
99103
!> Link executable
100104
procedure :: link
101105
!> Check whether compiler is recognized
@@ -583,6 +587,41 @@ subroutine get_default_c_compiler(f_compiler, c_compiler)
583587

584588
end subroutine get_default_c_compiler
585589

590+
!> Get C++ Compiler.
591+
subroutine get_default_cxx_compiler(f_compiler, cxx_compiler)
592+
character(len=*), intent(in) :: f_compiler
593+
character(len=:), allocatable, intent(out) :: cxx_compiler
594+
integer(compiler_enum) :: id
595+
596+
id = get_compiler_id(f_compiler)
597+
598+
select case(id)
599+
600+
case(id_intel_classic_nix, id_intel_classic_mac, id_intel_classic_windows)
601+
cxx_compiler = 'icpc'
602+
603+
case(id_intel_llvm_nix,id_intel_llvm_windows)
604+
cxx_compiler = 'icpx'
605+
606+
case(id_flang, id_flang_new, id_f18)
607+
cxx_compiler='clang'
608+
609+
case(id_ibmxl)
610+
cxx_compiler='xlc++'
611+
612+
case(id_lfortran)
613+
cxx_compiler = 'cc'
614+
615+
case(id_gcc)
616+
cxx_compiler = 'g++'
617+
618+
case default
619+
! Fall-back to using Fortran compiler
620+
cxx_compiler = f_compiler
621+
end select
622+
623+
end subroutine get_default_cxx_compiler
624+
586625

587626
function get_compiler_id(compiler) result(id)
588627
character(len=*), intent(in) :: compiler
@@ -754,13 +793,15 @@ end function enumerate_libraries
754793

755794

756795
!> Create new compiler instance
757-
subroutine new_compiler(self, fc, cc, echo, verbose)
796+
subroutine new_compiler(self, fc, cc, cxx, echo, verbose)
758797
!> New instance of the compiler
759798
type(compiler_t), intent(out) :: self
760799
!> Fortran compiler name or path
761800
character(len=*), intent(in) :: fc
762801
!> C compiler name or path
763802
character(len=*), intent(in) :: cc
803+
!> C++ Compiler name or path
804+
character(len=*), intent(in) :: cxx
764805
!> Echo compiler command
765806
logical, intent(in) :: echo
766807
!> Verbose mode: dump compiler output
@@ -776,6 +817,12 @@ subroutine new_compiler(self, fc, cc, echo, verbose)
776817
else
777818
call get_default_c_compiler(self%fc, self%cc)
778819
end if
820+
821+
if (len_trim(cxx) > 0) then
822+
self%cxx = cxx
823+
else
824+
call get_default_cxx_compiler(self%fc, self%cxx)
825+
end if
779826
end subroutine new_compiler
780827

781828

@@ -866,6 +913,24 @@ subroutine compile_c(self, input, output, args, log_file, stat)
866913
& echo=self%echo, verbose=self%verbose, redirect=log_file, exitstat=stat)
867914
end subroutine compile_c
868915

916+
!> Compile a CPP object
917+
subroutine compile_cpp(self, input, output, args, log_file, stat)
918+
!> Instance of the compiler object
919+
class(compiler_t), intent(in) :: self
920+
!> Source file input
921+
character(len=*), intent(in) :: input
922+
!> Output file of object
923+
character(len=*), intent(in) :: output
924+
!> Arguments for compiler
925+
character(len=*), intent(in) :: args
926+
!> Compiler output log file
927+
character(len=*), intent(in) :: log_file
928+
!> Status flag
929+
integer, intent(out) :: stat
930+
931+
call run(self%cxx // " -c " // input // " " // args // " -o " // output, &
932+
& echo=self%echo, verbose=self%verbose, redirect=log_file, exitstat=stat)
933+
end subroutine compile_cpp
869934

870935
!> Link an executable
871936
subroutine link(self, output, args, log_file, stat)

0 commit comments

Comments
 (0)