@@ -70,6 +70,8 @@ module fpm_command_line
70
70
character (len= :),allocatable :: compiler
71
71
character (len= :),allocatable :: profile
72
72
character (len= :),allocatable :: flag
73
+ character (len= :),allocatable :: cflag
74
+ character (len= :),allocatable :: ldflag
73
75
end type
74
76
75
77
type, extends(fpm_build_settings) :: fpm_run_settings
@@ -111,7 +113,46 @@ module fpm_command_line
111
113
& ' ' , ' fpm' , ' new' , ' build' , ' run' , &
112
114
& ' test' , ' runner' , ' install' , ' update' , ' list' , ' help' , ' version' ]
113
115
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
+ ]
115
156
116
157
contains
117
158
subroutine get_command_line_settings (cmd_settings )
@@ -123,6 +164,9 @@ subroutine get_command_line_settings(cmd_settings)
123
164
type (fpm_install_settings), allocatable :: install_settings
124
165
character (len= :), allocatable :: common_args, compiler_args, run_args, working_dir
125
166
167
+ character (len=* ), parameter :: fflags_env = " FFLAGS" , cflags_env = " CFLAGS" , &
168
+ & ldflags_env = " LDFLAGS" , flags_default = " "
169
+
126
170
call set_help()
127
171
! text for --version switch,
128
172
select case (get_os_type())
@@ -160,7 +204,9 @@ subroutine get_command_line_settings(cmd_settings)
160
204
compiler_args = &
161
205
' --profile " "' // &
162
206
' --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)// ' "'
164
210
165
211
! now set subcommand-specific help text and process commandline
166
212
! arguments. Then call subcommand routine
@@ -205,6 +251,8 @@ subroutine get_command_line_settings(cmd_settings)
205
251
& profile= val_profile,&
206
252
& compiler= val_compiler, &
207
253
& flag= val_flag, &
254
+ & cflag= val_cflag, &
255
+ & ldflag= val_ldflag, &
208
256
& example= lget(' example' ), &
209
257
& list= lget(' list' ),&
210
258
& name= names,&
@@ -224,6 +272,8 @@ subroutine get_command_line_settings(cmd_settings)
224
272
& profile= val_profile,&
225
273
& compiler= val_compiler, &
226
274
& flag= val_flag, &
275
+ & cflag= val_cflag, &
276
+ & ldflag= val_ldflag, &
227
277
& list= lget(' list' ),&
228
278
& show_model= lget(' show-model' ),&
229
279
& verbose= lget(' verbose' ) )
@@ -356,6 +406,8 @@ subroutine get_command_line_settings(cmd_settings)
356
406
profile= val_profile,&
357
407
compiler= val_compiler, &
358
408
flag= val_flag, &
409
+ cflag= val_cflag, &
410
+ ldflag= val_ldflag, &
359
411
no_rebuild= lget(' no-rebuild' ), &
360
412
verbose= lget(' verbose' ))
361
413
call get_char_arg(install_settings% prefix, ' prefix' )
@@ -403,6 +455,8 @@ subroutine get_command_line_settings(cmd_settings)
403
455
& profile= val_profile, &
404
456
& compiler= val_compiler, &
405
457
& flag= val_flag, &
458
+ & cflag= val_cflag, &
459
+ & ldflag= val_ldflag, &
406
460
& example= .false. , &
407
461
& list= lget(' list' ), &
408
462
& name= names, &
@@ -467,6 +521,8 @@ subroutine check_build_vals()
467
521
endif
468
522
469
523
val_flag = " " // sget(' flag' )
524
+ val_cflag = " " // sget(' c-flag' )
525
+ val_ldflag = " " // sget(' link-flag' )
470
526
val_profile = sget(' profile' )
471
527
472
528
end subroutine check_build_vals
@@ -645,12 +701,7 @@ subroutine set_help()
645
701
' high optimization and "debug" for full debug options.' ,&
646
702
' If --flag is not specified the "debug" flags are the' ,&
647
703
' 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, &
654
705
' --list List candidates instead of building or running them. On ' , &
655
706
' the fpm(1) command this shows a brief list of subcommands.' , &
656
707
' --runner CMD Provides a command to prefix program execution paths. ' , &
@@ -771,12 +822,7 @@ subroutine set_help()
771
822
' high optimization and "debug" for full debug options.' ,&
772
823
' If --flag is not specified the "debug" flags are the' ,&
773
824
' 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, &
780
826
' --compiler COMPILER_NAME Specify a compiler name. The default is ' , &
781
827
' "gfortran" unless set by the environment ' , &
782
828
' variable FC. ' , &
@@ -844,12 +890,7 @@ subroutine set_help()
844
890
' high optimization and "debug" for full debug options.' ,&
845
891
' If --flag is not specified the "debug" flags are the' ,&
846
892
' 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, &
853
894
' --compiler COMPILER_NAME Specify a compiler name. The default is ' , &
854
895
' "gfortran" unless set by the environment ' , &
855
896
' variable FC. ' , &
@@ -1025,12 +1066,7 @@ subroutine set_help()
1025
1066
' high optimization and "debug" for full debug options.' ,&
1026
1067
' If --flag is not specified the "debug" flags are the' ,&
1027
1068
' 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, &
1034
1070
' --compiler COMPILER_NAME Specify a compiler name. The default is ' , &
1035
1071
' "gfortran" unless set by the environment ' , &
1036
1072
' variable FC. ' , &
@@ -1098,12 +1134,7 @@ subroutine set_help()
1098
1134
' high optimization and "debug" for full debug options.' ,&
1099
1135
' If --flag is not specified the "debug" flags are the' ,&
1100
1136
' 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, &
1107
1138
' --no-rebuild do not rebuild project before installation' , &
1108
1139
' --prefix DIR path to installation directory (requires write access),' , &
1109
1140
' the default prefix on Unix systems is $HOME/.local' , &
@@ -1148,14 +1179,4 @@ function get_fc_env() result(fc)
1148
1179
fc = get_env(fc_env_long, get_env(fc_env, fc_default))
1149
1180
end function get_fc_env
1150
1181
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
-
1161
1182
end module fpm_command_line
0 commit comments