Skip to content

Commit de15905

Browse files
committed
refactor: rename cpp_compiler to cxx_compiler
1 parent 0235f3f commit de15905

File tree

3 files changed

+19
-19
lines changed

3 files changed

+19
-19
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-
& settings%cpp_compiler, 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

src/fpm_command_line.f90

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -74,7 +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
77+
character(len=:),allocatable :: cxx_compiler
7878
character(len=:),allocatable :: archiver
7979
character(len=:),allocatable :: profile
8080
character(len=:),allocatable :: flag
@@ -199,7 +199,7 @@ subroutine get_command_line_settings(cmd_settings)
199199
logical :: unix
200200
type(fpm_install_settings), allocatable :: install_settings
201201
character(len=:), allocatable :: common_args, compiler_args, run_args, working_dir, &
202-
& c_compiler, cpp_compiler, archiver
202+
& c_compiler, cxx_compiler, archiver
203203

204204
character(len=*), parameter :: fc_env = "FC", cc_env = "CC", ar_env = "AR", &
205205
& fflags_env = "FFLAGS", cflags_env = "CFLAGS", cxxflags_env = "CXXFLAGS", ldflags_env = "LDFLAGS", &
@@ -248,7 +248,7 @@ subroutine get_command_line_settings(cmd_settings)
248248
' --no-prune F' // &
249249
' --compiler "'//get_fpm_env(fc_env, fc_default)//'"' // &
250250
' --c-compiler "'//get_fpm_env(cc_env, cc_default)//'"' // &
251-
' --cpp-compiler "'//get_fpm_env(cxx_env, cxx_default)//'"' // &
251+
' --cxx-compiler "'//get_fpm_env(cxx_env, cxx_default)//'"' // &
252252
' --archiver "'//get_fpm_env(ar_env, ar_default)//'"' // &
253253
' --flag:: "'//get_fpm_env(fflags_env, flags_default)//'"' // &
254254
' --c-flag:: "'//get_fpm_env(cflags_env, flags_default)//'"' // &
@@ -291,7 +291,7 @@ subroutine get_command_line_settings(cmd_settings)
291291
enddo
292292

293293
c_compiler = sget('c-compiler')
294-
cpp_compiler = sget('cpp-compiler')
294+
cxx_compiler = sget('cxx-compiler')
295295
archiver = sget('archiver')
296296
allocate(fpm_run_settings :: cmd_settings)
297297
val_runner=sget('runner')
@@ -324,7 +324,7 @@ subroutine get_command_line_settings(cmd_settings)
324324
call check_build_vals()
325325

326326
c_compiler = sget('c-compiler')
327-
cpp_compiler = sget('cpp-compiler')
327+
cxx_compiler = sget('cxx-compiler')
328328
archiver = sget('archiver')
329329
allocate( fpm_build_settings :: cmd_settings )
330330
cmd_settings=fpm_build_settings( &
@@ -479,7 +479,7 @@ subroutine get_command_line_settings(cmd_settings)
479479
call check_build_vals()
480480

481481
c_compiler = sget('c-compiler')
482-
cpp_compiler = sget('cpp-compiler')
482+
cxx_compiler = sget('cxx-compiler')
483483
archiver = sget('archiver')
484484
allocate(install_settings)
485485
install_settings = fpm_install_settings(&
@@ -534,7 +534,7 @@ subroutine get_command_line_settings(cmd_settings)
534534
enddo
535535

536536
c_compiler = sget('c-compiler')
537-
cpp_compiler = sget('cpp-compiler')
537+
cxx_compiler = sget('cxx-compiler')
538538
archiver = sget('archiver')
539539
allocate(fpm_test_settings :: cmd_settings)
540540
val_runner=sget('runner')

src/fpm_compiler.f90

Lines changed: 11 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -588,39 +588,39 @@ subroutine get_default_c_compiler(f_compiler, c_compiler)
588588
end subroutine get_default_c_compiler
589589

590590
!> Get C++ Compiler.
591-
subroutine get_default_cpp_compiler(f_compiler, cpp_compiler)
591+
subroutine get_default_cxx_compiler(f_compiler, cxx_compiler)
592592
character(len=*), intent(in) :: f_compiler
593-
character(len=:), allocatable, intent(out) :: cpp_compiler
593+
character(len=:), allocatable, intent(out) :: cxx_compiler
594594
integer(compiler_enum) :: id
595595

596596
id = get_compiler_id(f_compiler)
597597

598598
select case(id)
599599

600600
case(id_intel_classic_nix, id_intel_classic_mac, id_intel_classic_windows)
601-
cpp_compiler = 'icpc'
601+
cxx_compiler = 'icpc'
602602

603603
case(id_intel_llvm_nix,id_intel_llvm_windows)
604-
cpp_compiler = 'icpx'
604+
cxx_compiler = 'icpx'
605605

606606
case(id_flang, id_flang_new, id_f18)
607-
cpp_compiler='clang'
607+
cxx_compiler='clang'
608608

609609
case(id_ibmxl)
610-
cpp_compiler='xlc++'
610+
cxx_compiler='xlc++'
611611

612612
case(id_lfortran)
613-
cpp_compiler = 'cc'
613+
cxx_compiler = 'cc'
614614

615615
case(id_gcc)
616-
cpp_compiler = 'g++'
616+
cxx_compiler = 'g++'
617617

618618
case default
619619
! Fall-back to using Fortran compiler
620-
cpp_compiler = f_compiler
620+
cxx_compiler = f_compiler
621621
end select
622622

623-
end subroutine get_default_cpp_compiler
623+
end subroutine get_default_cxx_compiler
624624

625625

626626
function get_compiler_id(compiler) result(id)
@@ -821,7 +821,7 @@ subroutine new_compiler(self, fc, cc, cxx, echo, verbose)
821821
if (len_trim(cxx) > 0) then
822822
self%cxx = cxx
823823
else
824-
call get_default_cpp_compiler(self%fc, self%cxx)
824+
call get_default_cxx_compiler(self%fc, self%cxx)
825825
end if
826826
end subroutine new_compiler
827827

0 commit comments

Comments
 (0)