Skip to content

Commit 26468d2

Browse files
committed
feat: added support for cpp files compilation
1 parent 1f2831f commit 26468d2

File tree

8 files changed

+177
-12
lines changed

8 files changed

+177
-12
lines changed

src/fpm.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -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%cpp_compiler, echo=settings%verbose, verbose=settings%verbose)
6969
call new_archiver(model%archiver, settings%archiver, &
7070
& echo=settings%verbose, verbose=settings%verbose)
7171

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: 9 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -74,6 +74,7 @@ module fpm_command_line
7474
logical :: prune=.true.
7575
character(len=:),allocatable :: compiler
7676
character(len=:),allocatable :: c_compiler
77+
character(len=:),allocatable :: cpp_compiler
7778
character(len=:),allocatable :: archiver
7879
character(len=:),allocatable :: profile
7980
character(len=:),allocatable :: flag
@@ -197,11 +198,12 @@ subroutine get_command_line_settings(cmd_settings)
197198
logical :: unix
198199
type(fpm_install_settings), allocatable :: install_settings
199200
character(len=:), allocatable :: common_args, compiler_args, run_args, working_dir, &
200-
& c_compiler, archiver
201+
& c_compiler, cpp_compiler, archiver
201202

202203
character(len=*), parameter :: fc_env = "FC", cc_env = "CC", ar_env = "AR", &
203204
& fflags_env = "FFLAGS", cflags_env = "CFLAGS", ldflags_env = "LDFLAGS", &
204-
& fc_default = "gfortran", cc_default = " ", ar_default = " ", flags_default = " "
205+
& fc_default = "gfortran", cc_default = " ", ar_default = " ", flags_default = " ", &
206+
& cppc_env = "CPPC", cppc_default = " "
205207
type(error_t), allocatable :: error
206208

207209
call set_help()
@@ -245,6 +247,7 @@ subroutine get_command_line_settings(cmd_settings)
245247
' --no-prune F' // &
246248
' --compiler "'//get_fpm_env(fc_env, fc_default)//'"' // &
247249
' --c-compiler "'//get_fpm_env(cc_env, cc_default)//'"' // &
250+
' --cpp-compiler "'//get_fpm_env(cppc_env, cppc_default)//'"' // &
248251
' --archiver "'//get_fpm_env(ar_env, ar_default)//'"' // &
249252
' --flag:: "'//get_fpm_env(fflags_env, flags_default)//'"' // &
250253
' --c-flag:: "'//get_fpm_env(cflags_env, flags_default)//'"' // &
@@ -286,6 +289,7 @@ subroutine get_command_line_settings(cmd_settings)
286289
enddo
287290

288291
c_compiler = sget('c-compiler')
292+
cpp_compiler = sget('cpp-compiler')
289293
archiver = sget('archiver')
290294
allocate(fpm_run_settings :: cmd_settings)
291295
val_runner=sget('runner')
@@ -317,6 +321,7 @@ subroutine get_command_line_settings(cmd_settings)
317321
call check_build_vals()
318322

319323
c_compiler = sget('c-compiler')
324+
cpp_compiler = sget('cpp-compiler')
320325
archiver = sget('archiver')
321326
allocate( fpm_build_settings :: cmd_settings )
322327
cmd_settings=fpm_build_settings( &
@@ -470,6 +475,7 @@ subroutine get_command_line_settings(cmd_settings)
470475
call check_build_vals()
471476

472477
c_compiler = sget('c-compiler')
478+
cpp_compiler = sget('cpp-compiler')
473479
archiver = sget('archiver')
474480
allocate(install_settings)
475481
install_settings = fpm_install_settings(&
@@ -523,6 +529,7 @@ subroutine get_command_line_settings(cmd_settings)
523529
enddo
524530

525531
c_compiler = sget('c-compiler')
532+
cpp_compiler = sget('cpp-compiler')
526533
archiver = sget('archiver')
527534
allocate(fpm_test_settings :: cmd_settings)
528535
val_runner=sget('runner')

src/fpm_compiler.f90

Lines changed: 61 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 :: cppc
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_cpp_compiler(f_compiler, c_compiler)
592+
character(len=*), intent(in) :: f_compiler
593+
character(len=:), allocatable, intent(out) :: c_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+
c_compiler = 'icpc'
602+
603+
case(id_intel_llvm_nix,id_intel_llvm_windows)
604+
c_compiler = 'icpx'
605+
606+
case(id_flang, id_flang_new, id_f18)
607+
c_compiler='clang'
608+
609+
case(id_ibmxl)
610+
c_compiler='xlc++'
611+
612+
case(id_lfortran)
613+
c_compiler = 'cc'
614+
615+
case(id_gcc)
616+
c_compiler = 'g++'
617+
618+
case default
619+
! Fall-back to using Fortran compiler
620+
c_compiler = f_compiler
621+
end select
622+
623+
end subroutine get_default_cpp_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, cppc, 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) :: cppc
764805
!> Echo compiler command
765806
logical, intent(in) :: echo
766807
!> Verbose mode: dump compiler output
@@ -775,6 +816,7 @@ subroutine new_compiler(self, fc, cc, echo, verbose)
775816
self%cc = cc
776817
else
777818
call get_default_c_compiler(self%fc, self%cc)
819+
call get_default_cpp_compiler(self%fc, self%cppc)
778820
end if
779821
end subroutine new_compiler
780822

@@ -866,6 +908,24 @@ subroutine compile_c(self, input, output, args, log_file, stat)
866908
& echo=self%echo, verbose=self%verbose, redirect=log_file, exitstat=stat)
867909
end subroutine compile_c
868910

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

870930
!> Link an executable
871931
subroutine link(self, output, args, log_file, stat)

src/fpm_model.f90

Lines changed: 6 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -47,7 +47,8 @@ module fpm_model
4747
public :: FPM_UNIT_UNKNOWN, FPM_UNIT_PROGRAM, FPM_UNIT_MODULE, &
4848
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, FPM_UNIT_CSOURCE, &
4949
FPM_UNIT_CHEADER, FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, &
50-
FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST
50+
FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST, &
51+
FPM_UNIT_CPPSOURCE
5152

5253
!> Source type unknown
5354
integer, parameter :: FPM_UNIT_UNKNOWN = -1
@@ -63,7 +64,8 @@ module fpm_model
6364
integer, parameter :: FPM_UNIT_CSOURCE = 5
6465
!> Source type is c header file
6566
integer, parameter :: FPM_UNIT_CHEADER = 6
66-
67+
!> Souce type is c++ source file.
68+
integer, parameter :: FPM_UNIT_CPPSOURCE = 7
6769

6870
!> Source has no module-use scope
6971
integer, parameter :: FPM_SCOPE_UNKNOWN = -1
@@ -254,6 +256,8 @@ function info_srcfile(source) result(s)
254256
s = s // "FPM_UNIT_SUBPROGRAM"
255257
case (FPM_UNIT_CSOURCE)
256258
s = s // "FPM_UNIT_CSOURCE"
259+
case (FPM_UNIT_CPPSOURCE)
260+
s = s // "FPM_UNIT_CPPSOURCE"
257261
case (FPM_UNIT_CHEADER)
258262
s = s // "FPM_UNIT_CHEADER"
259263
case default

src/fpm_source_parsing.f90

Lines changed: 77 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -21,12 +21,13 @@ module fpm_source_parsing
2121
FPM_UNIT_UNKNOWN, FPM_UNIT_PROGRAM, FPM_UNIT_MODULE, &
2222
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, &
2323
FPM_UNIT_CSOURCE, FPM_UNIT_CHEADER, FPM_SCOPE_UNKNOWN, &
24-
FPM_SCOPE_LIB, FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_TEST
24+
FPM_SCOPE_LIB, FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_TEST, &
25+
FPM_UNIT_CPPSOURCE
2526
use fpm_filesystem, only: read_lines, read_lines_expanded, exists
2627
implicit none
2728

2829
private
29-
public :: parse_f_source, parse_c_source
30+
public :: parse_f_source, parse_c_source, parse_cpp_source
3031

3132
character(15), parameter :: INTRINSIC_MODULE_NAMES(*) = &
3233
['iso_c_binding ', &
@@ -512,6 +513,80 @@ function parse_c_source(c_filename,error) result(c_source)
512513

513514
end function parse_c_source
514515

516+
!> Parsing of cpp source files
517+
!>
518+
!> The following statements are recognised and parsed:
519+
!>
520+
!> - `#include` preprocessor statement
521+
!>
522+
function parse_cpp_source(c_filename,error) result(cpp_source)
523+
character(*), intent(in) :: c_filename
524+
type(srcfile_t) :: cpp_source
525+
type(error_t), allocatable, intent(out) :: error
526+
527+
integer :: fh, n_include, i, pass, stat
528+
type(string_t), allocatable :: file_lines(:)
529+
530+
cpp_source%file_name = c_filename
531+
532+
if (str_ends_with(lower(c_filename), ".cpp")) then
533+
534+
cpp_source%unit_type = FPM_UNIT_CPPSOURCE
535+
536+
end if
537+
538+
allocate(cpp_source%modules_used(0))
539+
allocate(cpp_source%modules_provided(0))
540+
allocate(cpp_source%parent_modules(0))
541+
542+
open(newunit=fh,file=c_filename,status='old')
543+
file_lines = read_lines(fh)
544+
close(fh)
545+
546+
! Ignore empty files, returned as FPM_UNIT_UNKNOWN
547+
if (len_trim(file_lines) < 1) then
548+
cpp_source%unit_type = FPM_UNIT_UNKNOWN
549+
return
550+
end if
551+
552+
cpp_source%digest = fnv_1a(file_lines)
553+
554+
do pass = 1,2
555+
n_include = 0
556+
file_loop: do i=1,size(file_lines)
557+
558+
! Process 'INCLUDE' statements
559+
if (index(adjustl(lower(file_lines(i)%s)),'#include') == 1 .and. &
560+
index(file_lines(i)%s,'"') > 0) then
561+
562+
n_include = n_include + 1
563+
564+
if (pass == 2) then
565+
566+
cpp_source%include_dependencies(n_include)%s = &
567+
& split_n(file_lines(i)%s,n=2,delims='"',stat=stat)
568+
if (stat /= 0) then
569+
call file_parse_error(error,c_filename, &
570+
'unable to get cpp include file',i, &
571+
file_lines(i)%s,index(file_lines(i)%s,'"'))
572+
return
573+
end if
574+
575+
end if
576+
577+
end if
578+
579+
end do file_loop
580+
581+
if (pass == 1) then
582+
allocate(cpp_source%include_dependencies(n_include))
583+
end if
584+
585+
end do
586+
587+
end function parse_cpp_source
588+
589+
515590
!> Split a string on one or more delimeters
516591
!> and return the nth substring if it exists
517592
!>

src/fpm_sources.f90

Lines changed: 6 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,7 @@ module fpm_sources
88
use fpm_model, only: srcfile_t, FPM_UNIT_PROGRAM
99
use fpm_filesystem, only: basename, canon_path, dirname, join_path, list_files, is_hidden_file
1010
use fpm_strings, only: lower, str_ends_with, string_t, operator(.in.)
11-
use fpm_source_parsing, only: parse_f_source, parse_c_source
11+
use fpm_source_parsing, only: parse_f_source, parse_c_source, parse_cpp_source
1212
use fpm_manifest_executable, only: executable_config_t
1313
implicit none
1414

@@ -39,6 +39,10 @@ function parse_source(source_file_path,error) result(source)
3939

4040
source = parse_c_source(source_file_path,error)
4141

42+
else if (str_ends_with(lower(source_file_path), [".cpp"])) then
43+
44+
source = parse_cpp_source(source_file_path, error)
45+
4246
end if
4347

4448
if (allocated(error)) then
@@ -84,7 +88,7 @@ subroutine add_sources_from_dir(sources,directory,scope,with_executables,recurse
8488
is_source = [(.not.(is_hidden_file(basename(file_names(i)%s))) .and. &
8589
.not.(canon_path(file_names(i)%s) .in. existing_src_files) .and. &
8690
(str_ends_with(lower(file_names(i)%s), fortran_suffixes) .or. &
87-
str_ends_with(lower(file_names(i)%s),[".c",".h"]) ),i=1,size(file_names))]
91+
str_ends_with(lower(file_names(i)%s),[".c ",".h ", ".cpp"]) ),i=1,size(file_names))]
8892
src_file_names = pack(file_names,is_source)
8993

9094
allocate(dir_sources(size(src_file_names)))

src/fpm_targets.f90

Lines changed: 11 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -37,7 +37,7 @@ module fpm_targets
3737

3838
public FPM_TARGET_UNKNOWN, FPM_TARGET_EXECUTABLE, &
3939
FPM_TARGET_ARCHIVE, FPM_TARGET_OBJECT, &
40-
FPM_TARGET_C_OBJECT
40+
FPM_TARGET_C_OBJECT, FPM_TARGET_CPP_OBJECT
4141
public build_target_t, build_target_ptr
4242
public targets_from_sources, resolve_module_dependencies
4343
public resolve_target_linking, add_target, add_dependency
@@ -55,6 +55,8 @@ module fpm_targets
5555
integer, parameter :: FPM_TARGET_OBJECT = 3
5656
!> Target type is c compiled object
5757
integer, parameter :: FPM_TARGET_C_OBJECT = 4
58+
!> Target type is cpp compiled object
59+
integer, parameter :: FPM_TARGET_CPP_OBJECT = 5
5860

5961
!> Wrapper type for constructing arrays of `[[build_target_t]]` pointers
6062
type build_target_ptr
@@ -238,6 +240,14 @@ subroutine build_target_list(targets,model)
238240
call add_dependency(targets(1)%ptr, targets(size(targets))%ptr)
239241
end if
240242

243+
case (FPM_UNIT_CPPSOURCE)
244+
245+
call add_target(targets,package=model%packages(j)%name,source = sources(i), &
246+
type = FPM_UNIT_CPPSOURCE, &
247+
output_name = get_object_name(sources(i)), &
248+
macros = model%packages(j)%macros, &
249+
version = model%packages(j)%version)
250+
241251
case (FPM_UNIT_PROGRAM)
242252

243253
call add_target(targets,package=model%packages(j)%name,type = FPM_TARGET_OBJECT,&

0 commit comments

Comments
 (0)