Skip to content

Commit a4f3be5

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

File tree

4 files changed

+80
-46
lines changed

4 files changed

+80
-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: 63 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,46 @@ 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+
''
155+
]
115156

116157
contains
117158
subroutine get_command_line_settings(cmd_settings)
@@ -123,6 +164,9 @@ subroutine get_command_line_settings(cmd_settings)
123164
type(fpm_install_settings), allocatable :: install_settings
124165
character(len=:), allocatable :: common_args, compiler_args, run_args, working_dir
125166

167+
character(len=*), parameter :: fflags_env = "FFLAGS", cflags_env = "CFLAGS", &
168+
& ldflags_env = "LDFLAGS", flags_default = " "
169+
126170
call set_help()
127171
! text for --version switch,
128172
select case (get_os_type())
@@ -160,7 +204,9 @@ subroutine get_command_line_settings(cmd_settings)
160204
compiler_args = &
161205
' --profile " "' // &
162206
' --compiler "'//get_fc_env()//'"' // &
163-
' --flag:: "'//get_fflags_env()//'"'
207+
' --flag:: "'//get_env(fflags_env, flags_default)//'"' // &
208+
' --c-flag:: "'//get_env(cflags_env, flags_default)//'"' // &
209+
' --link-flag:: "'//get_env(ldflags_env, flags_default)//'"'
164210

165211
! now set subcommand-specific help text and process commandline
166212
! arguments. Then call subcommand routine
@@ -205,6 +251,8 @@ subroutine get_command_line_settings(cmd_settings)
205251
& profile=val_profile,&
206252
& compiler=val_compiler, &
207253
& flag=val_flag, &
254+
& cflag=val_cflag, &
255+
& ldflag=val_ldflag, &
208256
& example=lget('example'), &
209257
& list=lget('list'),&
210258
& name=names,&
@@ -224,6 +272,8 @@ subroutine get_command_line_settings(cmd_settings)
224272
& profile=val_profile,&
225273
& compiler=val_compiler, &
226274
& flag=val_flag, &
275+
& cflag=val_cflag, &
276+
& ldflag=val_ldflag, &
227277
& list=lget('list'),&
228278
& show_model=lget('show-model'),&
229279
& verbose=lget('verbose') )
@@ -356,6 +406,8 @@ subroutine get_command_line_settings(cmd_settings)
356406
profile=val_profile,&
357407
compiler=val_compiler, &
358408
flag=val_flag, &
409+
cflag=val_cflag, &
410+
ldflag=val_ldflag, &
359411
no_rebuild=lget('no-rebuild'), &
360412
verbose=lget('verbose'))
361413
call get_char_arg(install_settings%prefix, 'prefix')
@@ -403,6 +455,8 @@ subroutine get_command_line_settings(cmd_settings)
403455
& profile=val_profile, &
404456
& compiler=val_compiler, &
405457
& flag=val_flag, &
458+
& cflag=val_cflag, &
459+
& ldflag=val_ldflag, &
406460
& example=.false., &
407461
& list=lget('list'), &
408462
& name=names, &
@@ -467,6 +521,8 @@ subroutine check_build_vals()
467521
endif
468522

469523
val_flag = " " // sget('flag')
524+
val_cflag = " " // sget('c-flag')
525+
val_ldflag = " " // sget('link-flag')
470526
val_profile = sget('profile')
471527

472528
end subroutine check_build_vals
@@ -645,12 +701,7 @@ subroutine set_help()
645701
' high optimization and "debug" for full debug options.',&
646702
' If --flag is not specified the "debug" flags are the',&
647703
' 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.',&
704+
help_text_flag, &
654705
' --list List candidates instead of building or running them. On ', &
655706
' the fpm(1) command this shows a brief list of subcommands.', &
656707
' --runner CMD Provides a command to prefix program execution paths. ', &
@@ -771,12 +822,7 @@ subroutine set_help()
771822
' high optimization and "debug" for full debug options.',&
772823
' If --flag is not specified the "debug" flags are the',&
773824
' 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.',&
825+
help_text_flag, &
780826
' --compiler COMPILER_NAME Specify a compiler name. The default is ', &
781827
' "gfortran" unless set by the environment ', &
782828
' variable FC. ', &
@@ -844,12 +890,7 @@ subroutine set_help()
844890
' high optimization and "debug" for full debug options.',&
845891
' If --flag is not specified the "debug" flags are the',&
846892
' 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.',&
893+
help_text_flag, &
853894
' --compiler COMPILER_NAME Specify a compiler name. The default is ', &
854895
' "gfortran" unless set by the environment ', &
855896
' variable FC. ', &
@@ -1025,12 +1066,7 @@ subroutine set_help()
10251066
' high optimization and "debug" for full debug options.',&
10261067
' If --flag is not specified the "debug" flags are the',&
10271068
' 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.',&
1069+
help_text_flag, &
10341070
' --compiler COMPILER_NAME Specify a compiler name. The default is ', &
10351071
' "gfortran" unless set by the environment ', &
10361072
' variable FC. ', &
@@ -1098,12 +1134,7 @@ subroutine set_help()
10981134
' high optimization and "debug" for full debug options.',&
10991135
' If --flag is not specified the "debug" flags are the',&
11001136
' 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.',&
1137+
help_text_flag, &
11071138
' --no-rebuild do not rebuild project before installation', &
11081139
' --prefix DIR path to installation directory (requires write access),', &
11091140
' the default prefix on Unix systems is $HOME/.local', &
@@ -1148,14 +1179,4 @@ function get_fc_env() result(fc)
11481179
fc = get_env(fc_env_long, get_env(fc_env, fc_default))
11491180
end function get_fc_env
11501181

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-
11611182
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)