Skip to content

Commit ec88660

Browse files
committed
Allow usage of --c-flag / CFLAGS and --link-flag / LDFLAGS
1 parent 9bc3b78 commit ec88660

File tree

4 files changed

+89
-46
lines changed

4 files changed

+89
-46
lines changed

src/fpm.f90

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

4040
integer :: i, j
4141
type(package_config_t) :: dependency
42-
character(len=:), allocatable :: manifest, lib_dir, flags
42+
character(len=:), allocatable :: manifest, lib_dir, flags, cflags, ldflags
4343

4444
logical :: duplicates_found = .false.
4545
type(string_t) :: include_dir
@@ -73,7 +73,10 @@ subroutine build_model(model, settings, package, error)
7373
end select
7474
end if
7575

76-
write(build_name, '(z16.16)') fnv_1a(flags)
76+
cflags = trim(settings%cflag)
77+
ldflags = trim(settings%ldflag)
78+
79+
write(build_name, '(z16.16)') fnv_1a(flags//cflags//ldflags)
7780

7881
if (model%compiler%is_unknown()) then
7982
write(*, '(*(a:,1x))') &
@@ -195,6 +198,8 @@ subroutine build_model(model, settings, package, error)
195198
write(*,*)'<INFO> COMPILER: ',model%compiler%fc
196199
write(*,*)'<INFO> C COMPILER: ',model%compiler%cc
197200
write(*,*)'<INFO> COMPILER OPTIONS: ', model%fortran_compile_flags
201+
write(*,*)'<INFO> C COMPILER OPTIONS: ', model%c_compile_flags
202+
write(*,*)'<INFO> LINKER OPTIONS: ', model%link_flags
198203
write(*,*)'<INFO> INCLUDE DIRECTORIES: [', string_cat(model%include_dirs,','),']'
199204
end if
200205

src/fpm_command_line.f90

Lines changed: 72 additions & 42 deletions
Original file line numberDiff line numberDiff line change
@@ -70,6 +70,8 @@ module fpm_command_line
7070
character(len=:),allocatable :: compiler
7171
character(len=:),allocatable :: profile
7272
character(len=:),allocatable :: flag
73+
character(len=:),allocatable :: cflag
74+
character(len=:),allocatable :: ldflag
7375
end type
7476

7577
type, extends(fpm_build_settings) :: fpm_run_settings
@@ -111,7 +113,45 @@ module fpm_command_line
111113
& ' ', 'fpm', 'new', 'build', 'run', &
112114
& 'test', 'runner', 'install', 'update', 'list', 'help', 'version' ]
113115

114-
character(len=:), allocatable :: val_runner, val_compiler, val_flag, val_profile
116+
character(len=:), allocatable :: val_runner, val_compiler, val_flag, val_cflag, val_ldflag, &
117+
val_profile
118+
119+
character(len=80), parameter :: help_text_flag(*) = [character(len=80) :: &
120+
' --flag FFLAGS selects compile arguments for the build, the default',&
121+
' value is set by the FFLAGS environment variable.', &
122+
' These are added to the profile options if --profile', &
123+
' is specified, else these options override the defaults.',&
124+
' Note object and .mod directory locations are always',&
125+
' built in.',&
126+
' --c-flag CFLAGS selects compile arguments specific for C source in the build.',&
127+
' The default value is set by the CFLAGS environment variable.',&
128+
' --link-flag LDFLAGS',&
129+
' select arguments passed to the linker for the build.',&
130+
' The default value is set by the LDFLAGS environment variable.'&
131+
]
132+
133+
134+
character(len=80), parameter :: help_text_environment(*) = [character(len=80) :: &
135+
'ENVIRONMENT VARIABLES',&
136+
' FPM_COMPILER sets the path to the Fortran compiler used for the build,', &
137+
' will be overwritten by --compiler command line option', &
138+
'', &
139+
' FC sets the path to the Fortran compiler used for the build,', &
140+
' will be overwritten by FPM_COMPILER environment variable', &
141+
'', &
142+
' FFLAGS sets the arguments for the Fortran compiler', &
143+
' will be overwritten by --flag command line option', &
144+
'', &
145+
' CC sets the path to the C compiler used for the build,', &
146+
'', &
147+
' CFLAGS sets the arguments for the C compiler', &
148+
' will be overwritten by --c-flag command line option', &
149+
'', &
150+
' AR sets the path to the archiver used for the build,', &
151+
'', &
152+
' LDFLAGS sets additional link arguments for creating executables', &
153+
' will be overwritten by --link-flag command line option' &
154+
]
115155

116156
contains
117157
subroutine get_command_line_settings(cmd_settings)
@@ -123,6 +163,9 @@ subroutine get_command_line_settings(cmd_settings)
123163
type(fpm_install_settings), allocatable :: install_settings
124164
character(len=:), allocatable :: common_args, compiler_args, run_args, working_dir
125165

166+
character(len=*), parameter :: fflags_env = "FFLAGS", cflags_env = "CFLAGS", &
167+
& ldflags_env = "LDFLAGS", flags_default = " "
168+
126169
call set_help()
127170
! text for --version switch,
128171
select case (get_os_type())
@@ -160,7 +203,9 @@ subroutine get_command_line_settings(cmd_settings)
160203
compiler_args = &
161204
' --profile " "' // &
162205
' --compiler "'//get_fc_env()//'"' // &
163-
' --flag:: "'//get_fflags_env()//'"'
206+
' --flag:: "'//get_env(fflags_env, flags_default)//'"' // &
207+
' --c-flag:: "'//get_env(cflags_env, flags_default)//'"' // &
208+
' --link-flag:: "'//get_env(ldflags_env, flags_default)//'"'
164209

165210
! now set subcommand-specific help text and process commandline
166211
! arguments. Then call subcommand routine
@@ -205,6 +250,8 @@ subroutine get_command_line_settings(cmd_settings)
205250
& profile=val_profile,&
206251
& compiler=val_compiler, &
207252
& flag=val_flag, &
253+
& cflag=val_cflag, &
254+
& ldflag=val_ldflag, &
208255
& example=lget('example'), &
209256
& list=lget('list'),&
210257
& name=names,&
@@ -224,6 +271,8 @@ subroutine get_command_line_settings(cmd_settings)
224271
& profile=val_profile,&
225272
& compiler=val_compiler, &
226273
& flag=val_flag, &
274+
& cflag=val_cflag, &
275+
& ldflag=val_ldflag, &
227276
& list=lget('list'),&
228277
& show_model=lget('show-model'),&
229278
& verbose=lget('verbose') )
@@ -356,6 +405,8 @@ subroutine get_command_line_settings(cmd_settings)
356405
profile=val_profile,&
357406
compiler=val_compiler, &
358407
flag=val_flag, &
408+
cflag=val_cflag, &
409+
ldflag=val_ldflag, &
359410
no_rebuild=lget('no-rebuild'), &
360411
verbose=lget('verbose'))
361412
call get_char_arg(install_settings%prefix, 'prefix')
@@ -403,6 +454,8 @@ subroutine get_command_line_settings(cmd_settings)
403454
& profile=val_profile, &
404455
& compiler=val_compiler, &
405456
& flag=val_flag, &
457+
& cflag=val_cflag, &
458+
& ldflag=val_ldflag, &
406459
& example=.false., &
407460
& list=lget('list'), &
408461
& name=names, &
@@ -467,6 +520,8 @@ subroutine check_build_vals()
467520
endif
468521

469522
val_flag = " " // sget('flag')
523+
val_cflag = " " // sget('c-flag')
524+
val_ldflag = " " // sget('link-flag')
470525
val_profile = sget('profile')
471526

472527
end subroutine check_build_vals
@@ -645,12 +700,7 @@ subroutine set_help()
645700
' high optimization and "debug" for full debug options.',&
646701
' If --flag is not specified the "debug" flags are the',&
647702
' default. ',&
648-
' --flag FFLAGS selects compile arguments for the build, the default',&
649-
' value is set by the FFLAGS environment variable.', &
650-
' These are added to the profile options if --profile', &
651-
' is specified, else these options override the defaults.',&
652-
' Note object and .mod directory locations are always',&
653-
' built in.',&
703+
help_text_flag, &
654704
' --list List candidates instead of building or running them. On ', &
655705
' the fpm(1) command this shows a brief list of subcommands.', &
656706
' --runner CMD Provides a command to prefix program execution paths. ', &
@@ -694,6 +744,8 @@ subroutine set_help()
694744
' (currently) allow for continued lines or multiple specifications of ', &
695745
' the same option. ', &
696746
' ', &
747+
help_text_environment, &
748+
' ', &
697749
'EXAMPLES ', &
698750
' sample commands: ', &
699751
' ', &
@@ -771,12 +823,7 @@ subroutine set_help()
771823
' high optimization and "debug" for full debug options.',&
772824
' If --flag is not specified the "debug" flags are the',&
773825
' default. ',&
774-
' --flag FFLAGS selects compile arguments for the build, the default',&
775-
' value is set by the FFLAGS environment variable.', &
776-
' These are added to the profile options if --profile', &
777-
' is specified, else these options override the defaults.',&
778-
' Note object and .mod directory locations are always',&
779-
' built in.',&
826+
help_text_flag, &
780827
' --compiler COMPILER_NAME Specify a compiler name. The default is ', &
781828
' "gfortran" unless set by the environment ', &
782829
' variable FC. ', &
@@ -788,6 +835,8 @@ subroutine set_help()
788835
' -- ARGS optional arguments to pass to the program(s). The same ', &
789836
' arguments are passed to all program names specified. ', &
790837
' ', &
838+
help_text_environment, &
839+
' ', &
791840
'EXAMPLES ', &
792841
' fpm(1) - run or display project applications: ', &
793842
' ', &
@@ -844,12 +893,7 @@ subroutine set_help()
844893
' high optimization and "debug" for full debug options.',&
845894
' If --flag is not specified the "debug" flags are the',&
846895
' default. ',&
847-
' --flag FFLAGS selects compile arguments for the build, the default',&
848-
' value is set by the FFLAGS environment variable.', &
849-
' These are added to the profile options if --profile', &
850-
' is specified, else these options override the defaults.',&
851-
' Note object and .mod directory locations are always',&
852-
' built in.',&
896+
help_text_flag, &
853897
' --compiler COMPILER_NAME Specify a compiler name. The default is ', &
854898
' "gfortran" unless set by the environment ', &
855899
' variable FC. ', &
@@ -858,6 +902,8 @@ subroutine set_help()
858902
' --help print this help and exit ', &
859903
' --version print program version information and exit ', &
860904
' ', &
905+
help_text_environment, &
906+
' ', &
861907
'EXAMPLES ', &
862908
' Sample commands: ', &
863909
' ', &
@@ -1025,12 +1071,7 @@ subroutine set_help()
10251071
' high optimization and "debug" for full debug options.',&
10261072
' If --flag is not specified the "debug" flags are the',&
10271073
' default. ',&
1028-
' --flag FFLAGS selects compile arguments for the build, the default',&
1029-
' value is set by the FFLAGS environment variable.', &
1030-
' These are added to the profile options if --profile', &
1031-
' is specified, else these options override the defaults.',&
1032-
' Note object and .mod directory locations are always',&
1033-
' built in.',&
1074+
help_text_flag, &
10341075
' --compiler COMPILER_NAME Specify a compiler name. The default is ', &
10351076
' "gfortran" unless set by the environment ', &
10361077
' variable FC. ', &
@@ -1041,6 +1082,8 @@ subroutine set_help()
10411082
' The same arguments are passed to all test names ', &
10421083
' specified. ', &
10431084
' ', &
1085+
help_text_environment, &
1086+
' ', &
10441087
'EXAMPLES ', &
10451088
'run tests ', &
10461089
' ', &
@@ -1098,12 +1141,7 @@ subroutine set_help()
10981141
' high optimization and "debug" for full debug options.',&
10991142
' If --flag is not specified the "debug" flags are the',&
11001143
' default. ',&
1101-
' --flag FFLAGS selects compile arguments for the build, the default',&
1102-
' value is set by the FFLAGS environment variable.', &
1103-
' These are added to the profile options if --profile', &
1104-
' is specified, else these options override the defaults.',&
1105-
' Note object and .mod directory locations are always',&
1106-
' built in.',&
1144+
help_text_flag, &
11071145
' --no-rebuild do not rebuild project before installation', &
11081146
' --prefix DIR path to installation directory (requires write access),', &
11091147
' the default prefix on Unix systems is $HOME/.local', &
@@ -1115,6 +1153,8 @@ subroutine set_help()
11151153
' (default: include)', &
11161154
' --verbose print more information', &
11171155
'', &
1156+
help_text_environment, &
1157+
'', &
11181158
'EXAMPLES', &
11191159
' 1. Install release version of project:', &
11201160
'', &
@@ -1148,14 +1188,4 @@ function get_fc_env() result(fc)
11481188
fc = get_env(fc_env_long, get_env(fc_env, fc_default))
11491189
end function get_fc_env
11501190

1151-
!> Get Fortran compiler arguments from environment.
1152-
function get_fflags_env() result(fflags)
1153-
character(len=:), allocatable :: fflags
1154-
1155-
character(len=*), parameter :: fflags_env = "FFLAGS"
1156-
character(len=*), parameter :: fflags_default = " "
1157-
1158-
fflags = get_env(fflags_env, fflags_default)
1159-
end function get_fflags_env
1160-
11611191
end module fpm_command_line

src/fpm_model.f90

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -124,6 +124,12 @@ module fpm_model
124124
!> Command line flags passed to fortran for compilation
125125
character(:), allocatable :: fortran_compile_flags
126126

127+
!> Command line flags passed to C for compilation
128+
character(:), allocatable :: c_compile_flags
129+
130+
!> Command line flags passed to the linker
131+
character(:), allocatable :: link_flags
132+
127133
!> Base directory for build
128134
character(:), allocatable :: output_directory
129135

@@ -273,6 +279,8 @@ function info_model(model) result(s)
273279
s = s // ', archiver=(' // debug(model%archiver) // ')'
274280
! character(:), allocatable :: fortran_compile_flags
275281
s = s // ', fortran_compile_flags="' // model%fortran_compile_flags // '"'
282+
s = s // ', c_compile_flags="' // model%c_compile_flags // '"'
283+
s = s // ', link_flags="' // model%link_flags // '"'
276284
! character(:), allocatable :: output_directory
277285
s = s // ', output_directory="' // model%output_directory // '"'
278286
! type(string_t), allocatable :: link_libraries(:)

src/fpm_targets.f90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -479,7 +479,7 @@ subroutine resolve_target_linking(targets, model)
479479
if (target%target_type /= FPM_TARGET_C_OBJECT) then
480480
target%compile_flags = model%fortran_compile_flags//" "//global_include_flags
481481
else
482-
target%compile_flags = global_include_flags
482+
target%compile_flags = model%c_compile_flags//" "//global_include_flags
483483
end if
484484

485485
allocate(target%link_objects(0))
@@ -494,7 +494,7 @@ subroutine resolve_target_linking(targets, model)
494494

495495
call get_link_objects(target%link_objects,target,is_exe=.true.)
496496

497-
target%link_flags = string_cat(target%link_objects," ")
497+
target%link_flags = model%link_flags//" "//string_cat(target%link_objects," ")
498498

499499
if (allocated(target%link_libraries)) then
500500
if (size(target%link_libraries) > 0) then

0 commit comments

Comments
 (0)