Skip to content

Commit 5100827

Browse files
committed
refactor: added requested changes
1 parent 97ea8ce commit 5100827

File tree

7 files changed

+37
-10
lines changed

7 files changed

+37
-10
lines changed

ci/run_tests.sh

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -127,7 +127,7 @@ pushd preprocess_hello
127127
popd
128128

129129
pushd cpp_files
130-
"$fpm" build
130+
"$fpm" test
131131
popd
132132

133133
# Cleanup

src/fpm.f90

Lines changed: 3 additions & 1 deletion
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.
@@ -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%cpp_compile_flags = cxxflags
9698
model%link_flags = ldflags
9799

98100
model%include_tests = settings%build_tests

src/fpm_command_line.f90

Lines changed: 9 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -79,6 +79,7 @@ module fpm_command_line
7979
character(len=:),allocatable :: profile
8080
character(len=:),allocatable :: flag
8181
character(len=:),allocatable :: cflag
82+
character(len=:),allocatable :: cxxflag
8283
character(len=:),allocatable :: ldflag
8384
end type
8485

@@ -129,7 +130,7 @@ module fpm_command_line
129130
& ' ', 'fpm', 'new', 'build', 'run', 'clean', &
130131
& 'test', 'runner', 'install', 'update', 'list', 'help', 'version' ]
131132

132-
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, &
133134
val_profile
134135

135136
! '12345678901234567890123456789012345678901234567890123456789012345678901234567890',&
@@ -201,7 +202,7 @@ subroutine get_command_line_settings(cmd_settings)
201202
& c_compiler, cpp_compiler, archiver
202203

203204
character(len=*), parameter :: fc_env = "FC", cc_env = "CC", ar_env = "AR", &
204-
& fflags_env = "FFLAGS", cflags_env = "CFLAGS", ldflags_env = "LDFLAGS", &
205+
& fflags_env = "FFLAGS", cflags_env = "CFLAGS", cxxflags_env = "CXXFLAGS", ldflags_env = "LDFLAGS", &
205206
& fc_default = "gfortran", cc_default = " ", ar_default = " ", flags_default = " ", &
206207
& cxx_env = "CXX", cxx_default = " "
207208
type(error_t), allocatable :: error
@@ -251,6 +252,7 @@ subroutine get_command_line_settings(cmd_settings)
251252
' --archiver "'//get_fpm_env(ar_env, ar_default)//'"' // &
252253
' --flag:: "'//get_fpm_env(fflags_env, flags_default)//'"' // &
253254
' --c-flag:: "'//get_fpm_env(cflags_env, flags_default)//'"' // &
255+
' --cxx-flag:: "'//get_fpm_env(cxxflags_env, flags_default)//'"' // &
254256
' --link-flag:: "'//get_fpm_env(ldflags_env, flags_default)//'"'
255257

256258
! now set subcommand-specific help text and process commandline
@@ -303,6 +305,7 @@ subroutine get_command_line_settings(cmd_settings)
303305
& archiver=archiver, &
304306
& flag=val_flag, &
305307
& cflag=val_cflag, &
308+
& cxxflag=val_cxxflag, &
306309
& ldflag=val_ldflag, &
307310
& example=lget('example'), &
308311
& list=lget('list'),&
@@ -332,6 +335,7 @@ subroutine get_command_line_settings(cmd_settings)
332335
& archiver=archiver, &
333336
& flag=val_flag, &
334337
& cflag=val_cflag, &
338+
& cxxflag=val_cxxflag, &
335339
& ldflag=val_ldflag, &
336340
& list=lget('list'),&
337341
& show_model=lget('show-model'),&
@@ -487,6 +491,7 @@ subroutine get_command_line_settings(cmd_settings)
487491
archiver=archiver, &
488492
flag=val_flag, &
489493
cflag=val_cflag, &
494+
cxxflag=val_cxxflag, &
490495
ldflag=val_ldflag, &
491496
no_rebuild=lget('no-rebuild'), &
492497
verbose=lget('verbose'))
@@ -543,6 +548,7 @@ subroutine get_command_line_settings(cmd_settings)
543548
& archiver=archiver, &
544549
& flag=val_flag, &
545550
& cflag=val_cflag, &
551+
& cxxflag=val_cxxflag, &
546552
& ldflag=val_ldflag, &
547553
& example=.false., &
548554
& list=lget('list'), &
@@ -623,6 +629,7 @@ subroutine check_build_vals()
623629

624630
val_flag = " " // sget('flag')
625631
val_cflag = " " // sget('c-flag')
632+
val_cxxflag = " "// sget('cxx-flag')
626633
val_ldflag = " " // sget('link-flag')
627634
val_profile = sget('profile')
628635

src/fpm_compiler.f90

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -816,6 +816,11 @@ subroutine new_compiler(self, fc, cc, cxx, echo, verbose)
816816
self%cc = cc
817817
else
818818
call get_default_c_compiler(self%fc, self%cc)
819+
end if
820+
821+
if (len_trim(cxx) > 0) then
822+
self%cxx = cxx
823+
else
819824
call get_default_cpp_compiler(self%fc, self%cxx)
820825
end if
821826
end subroutine new_compiler

src/fpm_model.f90

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -155,6 +155,9 @@ module fpm_model
155155
!> Command line flags passed to C for compilation
156156
character(:), allocatable :: c_compile_flags
157157

158+
!> Command line flags passed to C++ for compilation
159+
character(:), allocatable :: cpp_compile_flags
160+
158161
!> Command line flags passed to the linker
159162
character(:), allocatable :: link_flags
160163

@@ -319,6 +322,7 @@ function info_model(model) result(s)
319322
! character(:), allocatable :: fortran_compile_flags
320323
s = s // ', fortran_compile_flags="' // model%fortran_compile_flags // '"'
321324
s = s // ', c_compile_flags="' // model%c_compile_flags // '"'
325+
s = s // ', cpp_compile_flags="' // model%cpp_compile_flags // '"'
322326
s = s // ', link_flags="' // model%link_flags // '"'
323327
s = s // ', build_prefix="' // model%build_prefix // '"'
324328
! type(string_t), allocatable :: link_libraries(:)

src/fpm_sources.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -85,7 +85,7 @@ subroutine add_sources_from_dir(sources,directory,scope,with_executables,recurse
8585
is_source = [(.not.(is_hidden_file(basename(file_names(i)%s))) .and. &
8686
.not.(canon_path(file_names(i)%s) .in. existing_src_files) .and. &
8787
(str_ends_with(lower(file_names(i)%s), fortran_suffixes) .or. &
88-
str_ends_with(lower(file_names(i)%s),[".c ",".h ", ".cpp"]) ),i=1,size(file_names))]
88+
str_ends_with(lower(file_names(i)%s), c_suffixes) ),i=1,size(file_names))]
8989
src_file_names = pack(file_names,is_source)
9090

9191
allocate(dir_sources(size(src_file_names)))

src/fpm_targets.f90

Lines changed: 14 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -243,13 +243,20 @@ subroutine build_target_list(targets,model)
243243
case (FPM_UNIT_CPPSOURCE)
244244

245245
call add_target(targets,package=model%packages(j)%name,source = sources(i), &
246-
type = FPM_UNIT_CPPSOURCE, &
246+
type = FPM_TARGET_CPP_OBJECT, &
247247
output_name = get_object_name(sources(i)), &
248248
macros = model%packages(j)%macros, &
249249
version = model%packages(j)%version)
250250

251-
!> Add stdc++ as a linker flag.
252-
model%link_flags = model%link_flags // "stdc++"
251+
if (with_lib .and. sources(i)%unit_scope == FPM_SCOPE_LIB) then
252+
! Archive depends on object
253+
call add_dependency(targets(1)%ptr, targets(size(targets))%ptr)
254+
end if
255+
256+
!> Add stdc++ as a linker flag. If not already there.
257+
if (.not. ("stdc++" .in. model%link_libraries)) then
258+
model%link_libraries = [model%link_libraries, string_t("stdc++")]
259+
end if
253260

254261
case (FPM_UNIT_PROGRAM)
255262

@@ -725,10 +732,12 @@ subroutine resolve_target_linking(targets, model)
725732
do i=1,size(targets)
726733

727734
associate(target => targets(i)%ptr)
728-
if (target%target_type /= FPM_TARGET_C_OBJECT) then
735+
if (target%target_type /= FPM_TARGET_C_OBJECT .and. target%target_type /= FPM_TARGET_CPP_OBJECT) then
729736
target%compile_flags = model%fortran_compile_flags
730-
else
737+
else if (target%target_type == FPM_TARGET_C_OBJECT) then
731738
target%compile_flags = model%c_compile_flags
739+
else if(target%target_type == FPM_TARGET_CPP_OBJECT) then
740+
target%compile_flags = model%cpp_compile_flags
732741
end if
733742

734743
!> Get macros as flags.

0 commit comments

Comments
 (0)