Skip to content

Commit 9bc3b78

Browse files
committed
Use environment variables for Fortran compiler and arguments
- Read Fortran compiler from FC (overwritten by FPM_COMPILER for compatibility) - Read Fortran compiler options from FFLAGS - Read C compiler from CC (remove FPM_C_COMPILER since it was never documented) - Read archiver from AR
1 parent 04da9a1 commit 9bc3b78

File tree

2 files changed

+77
-59
lines changed

2 files changed

+77
-59
lines changed

src/fpm_command_line.f90

Lines changed: 68 additions & 55 deletions
Original file line numberDiff line numberDiff line change
@@ -121,7 +121,7 @@ subroutine get_command_line_settings(cmd_settings)
121121
integer :: i
122122
integer :: widest
123123
type(fpm_install_settings), allocatable :: install_settings
124-
character(len=:), allocatable :: common_args, working_dir
124+
character(len=:), allocatable :: common_args, compiler_args, run_args, working_dir
125125

126126
call set_help()
127127
! text for --version switch,
@@ -148,23 +148,28 @@ subroutine get_command_line_settings(cmd_settings)
148148
CLI_RESPONSE_FILE=.true.
149149
cmdarg = get_subcommand()
150150

151-
common_args = '--directory:C " " '
151+
common_args = &
152+
' --directory:C " "' // &
153+
' --verbose F'
154+
155+
run_args = &
156+
' --target " "' // &
157+
' --list F' // &
158+
' --runner " "'
159+
160+
compiler_args = &
161+
' --profile " "' // &
162+
' --compiler "'//get_fc_env()//'"' // &
163+
' --flag:: "'//get_fflags_env()//'"'
152164

153165
! now set subcommand-specific help text and process commandline
154166
! arguments. Then call subcommand routine
155167
select case(trim(cmdarg))
156168

157169
case('run')
158-
call set_args(common_args //'&
159-
& --target " " &
160-
& --list F &
170+
call set_args(common_args // compiler_args // run_args //'&
161171
& --all F &
162-
& --profile " "&
163172
& --example F&
164-
& --runner " " &
165-
& --compiler "'//get_env('FPM_COMPILER','gfortran')//'" &
166-
& --flag:: " "&
167-
& --verbose F&
168173
& --',help_run,version_text)
169174

170175
call check_build_vals()
@@ -207,13 +212,9 @@ subroutine get_command_line_settings(cmd_settings)
207212
& verbose=lget('verbose') )
208213

209214
case('build')
210-
call set_args(common_args // '&
211-
& --profile " " &
215+
call set_args(common_args // compiler_args //'&
212216
& --list F &
213217
& --show-model F &
214-
& --compiler "'//get_env('FPM_COMPILER','gfortran')//'" &
215-
& --flag:: " "&
216-
& --verbose F&
217218
& --',help_build,version_text)
218219

219220
call check_build_vals()
@@ -236,8 +237,7 @@ subroutine get_command_line_settings(cmd_settings)
236237
& --example F &
237238
& --backfill F &
238239
& --full F &
239-
& --bare F &
240-
& --verbose:V F',&
240+
& --bare F', &
241241
& help_new, version_text)
242242
select case(size(unnamed))
243243
case(1)
@@ -296,9 +296,7 @@ subroutine get_command_line_settings(cmd_settings)
296296
endif
297297

298298
case('help','manual')
299-
call set_args(common_args // '&
300-
& --verbose F &
301-
& ',help_help,version_text)
299+
call set_args(common_args, help_help,version_text)
302300
if(size(unnamed).lt.2)then
303301
if(unnamed(1).eq.'help')then
304302
unnamed=[' ', 'fpm']
@@ -344,11 +342,9 @@ subroutine get_command_line_settings(cmd_settings)
344342
call printhelp(help_text)
345343

346344
case('install')
347-
call set_args(common_args // '&
348-
& --profile " " --no-rebuild F --verbose F --prefix " " &
345+
call set_args(common_args // compiler_args // '&
346+
& --no-rebuild F --prefix " " &
349347
& --list F &
350-
& --compiler "'//get_env('FPM_COMPILER','gfortran')//'" &
351-
& --flag:: " "&
352348
& --libdir "lib" --bindir "bin" --includedir "include"', &
353349
help_install, version_text)
354350

@@ -371,22 +367,14 @@ subroutine get_command_line_settings(cmd_settings)
371367
case('list')
372368
call set_args(common_args // '&
373369
& --list F&
374-
& --verbose F&
375370
&', help_list, version_text)
376371
call printhelp(help_list_nodash)
377372
if(lget('list'))then
378373
call printhelp(help_list_dash)
379374
endif
380375
case('test')
381-
call set_args(common_args // '&
382-
& --target " " &
383-
& --list F&
384-
& --profile " "&
385-
& --runner " " &
386-
& --compiler "'//get_env('FPM_COMPILER','gfortran')//'" &
387-
& --flag:: " "&
388-
& --verbose F&
389-
& --',help_test,version_text)
376+
call set_args(common_args // compiler_args // run_args // ' --', &
377+
help_test,version_text)
390378

391379
call check_build_vals()
392380

@@ -422,7 +410,7 @@ subroutine get_command_line_settings(cmd_settings)
422410
& verbose=lget('verbose') )
423411

424412
case('update')
425-
call set_args(common_args // ' --fetch-only F --verbose F --clean F', &
413+
call set_args(common_args // ' --fetch-only F --clean F', &
426414
help_update, version_text)
427415

428416
if( size(unnamed) .gt. 1 )then
@@ -443,7 +431,6 @@ subroutine get_command_line_settings(cmd_settings)
443431
else
444432
call set_args('&
445433
& --list F&
446-
& --verbose F&
447434
&', help_fpm, version_text)
448435
! Note: will not get here if --version or --usage or --help
449436
! is present on commandline
@@ -658,16 +645,17 @@ subroutine set_help()
658645
' high optimization and "debug" for full debug options.',&
659646
' If --flag is not specified the "debug" flags are the',&
660647
' default. ',&
661-
' --flag FFLAGS selects compile arguments for the build. These are',&
662-
' added to the profile options if --profile is specified,',&
663-
' else these options override the defaults.',&
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.',&
664652
' Note object and .mod directory locations are always',&
665653
' built in.',&
666654
' --list List candidates instead of building or running them. On ', &
667655
' the fpm(1) command this shows a brief list of subcommands.', &
668656
' --runner CMD Provides a command to prefix program execution paths. ', &
669657
' --compiler COMPILER_NAME Compiler name. The environment variable ', &
670-
' FPM_COMPILER sets the default. ', &
658+
' FC sets the default. ', &
671659
' -- ARGS Arguments to pass to executables. ', &
672660
' ', &
673661
'VALID FOR ALL SUBCOMMANDS ', &
@@ -783,14 +771,15 @@ subroutine set_help()
783771
' high optimization and "debug" for full debug options.',&
784772
' If --flag is not specified the "debug" flags are the',&
785773
' default. ',&
786-
' --flag FFLAGS selects compile arguments for the build. These are',&
787-
' added to the profile options if --profile is specified,',&
788-
' else these options override the defaults.',&
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.',&
789778
' Note object and .mod directory locations are always',&
790779
' built in.',&
791780
' --compiler COMPILER_NAME Specify a compiler name. The default is ', &
792781
' "gfortran" unless set by the environment ', &
793-
' variable FPM_COMPILER. ', &
782+
' variable FC. ', &
794783
' --runner CMD A command to prefix the program execution paths with. ', &
795784
' see "fpm help runner" for further details. ', &
796785
' --list list pathname of candidates instead of running them. Note ', &
@@ -855,14 +844,15 @@ subroutine set_help()
855844
' high optimization and "debug" for full debug options.',&
856845
' If --flag is not specified the "debug" flags are the',&
857846
' default. ',&
858-
' --flag FFLAGS selects compile arguments for the build. These are',&
859-
' added to the profile options if --profile is specified,',&
860-
' else these options override the defaults.',&
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.',&
861851
' Note object and .mod directory locations are always',&
862852
' built in.',&
863853
' --compiler COMPILER_NAME Specify a compiler name. The default is ', &
864854
' "gfortran" unless set by the environment ', &
865-
' variable FPM_COMPILER. ', &
855+
' variable FC. ', &
866856
' --list list candidates instead of building or running them ', &
867857
' --show-model show the model and exit (do not build) ', &
868858
' --help print this help and exit ', &
@@ -1035,14 +1025,15 @@ subroutine set_help()
10351025
' high optimization and "debug" for full debug options.',&
10361026
' If --flag is not specified the "debug" flags are the',&
10371027
' default. ',&
1038-
' --flag FFLAGS selects compile arguments for the build. These are',&
1039-
' added to the profile options if --profile is specified,',&
1040-
' else these options override the defaults.',&
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.',&
10411032
' Note object and .mod directory locations are always',&
10421033
' built in.',&
10431034
' --compiler COMPILER_NAME Specify a compiler name. The default is ', &
10441035
' "gfortran" unless set by the environment ', &
1045-
' variable FPM_COMPILER. ', &
1036+
' variable FC. ', &
10461037
' --runner CMD A command to prefix the program execution paths with. ', &
10471038
' see "fpm help runner" for further details. ', &
10481039
' --list list candidates instead of building or running them ', &
@@ -1107,9 +1098,10 @@ subroutine set_help()
11071098
' high optimization and "debug" for full debug options.',&
11081099
' If --flag is not specified the "debug" flags are the',&
11091100
' default. ',&
1110-
' --flag FFLAGS selects compile arguments for the build. These are',&
1111-
' added to the profile options if --profile is specified,',&
1112-
' else these options override the defaults.',&
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.',&
11131105
' Note object and .mod directory locations are always',&
11141106
' built in.',&
11151107
' --no-rebuild do not rebuild project before installation', &
@@ -1145,4 +1137,25 @@ subroutine get_char_arg(var, arg)
11451137
if (len_trim(var) == 0) deallocate(var)
11461138
end subroutine get_char_arg
11471139

1140+
1141+
!> Get Fortran compiler from environment.
1142+
function get_fc_env() result(fc)
1143+
character(len=:), allocatable :: fc
1144+
1145+
character(len=*), parameter :: fc_env = "FC", fc_env_long = "FPM_COMPILER"
1146+
character(len=*), parameter :: fc_default = "gfortran"
1147+
1148+
fc = get_env(fc_env_long, get_env(fc_env, fc_default))
1149+
end function get_fc_env
1150+
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+
11481161
end module fpm_command_line

src/fpm_compiler.f90

Lines changed: 9 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -602,7 +602,7 @@ subroutine new_compiler(self, fc)
602602
!> New instance of the compiler
603603
type(compiler_t), intent(out) :: self
604604

605-
character(len=*), parameter :: cc_env = "FPM_C_COMPILER"
605+
character(len=*), parameter :: cc_env = "CC"
606606

607607
self%id = get_compiler_id(fc)
608608

@@ -618,16 +618,21 @@ subroutine new_archiver(self)
618618
type(archiver_t), intent(out) :: self
619619
integer :: estat, os_type
620620

621+
character(len=:), allocatable :: ar
622+
character(len=*), parameter :: arflags = " -rs "
623+
624+
ar = get_env("AR", "ar")
625+
621626
os_type = get_os_type()
622627
if (os_type /= OS_WINDOWS .and. os_type /= OS_UNKNOWN) then
623-
self%ar = "ar -rs "
628+
self%ar = ar//arflags
624629
else
625-
call execute_command_line("ar --version > "//get_temp_filename()//" 2>&1", &
630+
call execute_command_line(ar//" --version > "//get_temp_filename()//" 2>&1", &
626631
& exitstat=estat)
627632
if (estat /= 0) then
628633
self%ar = "lib /OUT:"
629634
else
630-
self%ar = "ar -rs "
635+
self%ar = ar//arflags
631636
end if
632637
end if
633638
self%use_response_file = os_type == OS_WINDOWS

0 commit comments

Comments
 (0)