aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorSebastian Ehlert <28669218+awvwgk@users.noreply.github.com>2021-09-23 21:42:56 +0200
committerGitHub <noreply@github.com>2021-09-23 21:42:56 +0200
commitdfeb17a3811054716828be47644ac98b146746de (patch)
tree7b927b16a5307ef145912e13f1ac33a58295ef6a
parent6bb5f6c49a22e8cf342e1c71262d155195d2c64a (diff)
downloadfpm-dfeb17a3811054716828be47644ac98b146746de.tar.gz
fpm-dfeb17a3811054716828be47644ac98b146746de.zip
Allow setting, archiver, C compiler flags and linker flags from commandline (#549)
- Read Fortran compiler from FPM_FC or --compiler (deprecate FPM_COMPILER) - Read Fortran compiler options from FPM_FFLAGS or --flag - Read C compiler from FPM_CC or --c-compiler (deprecate FPM_C_COMPILER) - Read C compiler options from FPM_CFLAGS or --c-flag - Read archiver from FPM_AR or --archiver - Read linker options from FPM_LDFLAGS or --link-flag
-rw-r--r--src/fpm.f9013
-rw-r--r--src/fpm_command_line.f90214
-rw-r--r--src/fpm_compiler.f9051
-rw-r--r--src/fpm_model.f908
-rw-r--r--src/fpm_targets.f904
5 files changed, 197 insertions, 93 deletions
diff --git a/src/fpm.f90 b/src/fpm.f90
index 1449dc2..d8381ae 100644
--- a/src/fpm.f90
+++ b/src/fpm.f90
@@ -39,7 +39,7 @@ subroutine build_model(model, settings, package, error)
integer :: i, j
type(package_config_t) :: dependency
- character(len=:), allocatable :: manifest, lib_dir, flags
+ character(len=:), allocatable :: manifest, lib_dir, flags, cflags, ldflags
logical :: duplicates_found = .false.
type(string_t) :: include_dir
@@ -60,8 +60,8 @@ subroutine build_model(model, settings, package, error)
call filewrite(join_path("build", ".gitignore"),["*"])
end if
- call new_compiler(model%compiler, settings%compiler)
- call new_archiver(model%archiver)
+ call new_compiler(model%compiler, settings%compiler, settings%c_compiler)
+ call new_archiver(model%archiver, settings%archiver)
if (settings%flag == '') then
flags = model%compiler%get_default_flags(settings%profile == "release")
@@ -73,7 +73,10 @@ subroutine build_model(model, settings, package, error)
end select
end if
- write(build_name, '(z16.16)') fnv_1a(flags)
+ cflags = trim(settings%cflag)
+ ldflags = trim(settings%ldflag)
+
+ write(build_name, '(z16.16)') fnv_1a(flags//cflags//ldflags)
if (model%compiler%is_unknown()) then
write(*, '(*(a:,1x))') &
@@ -197,6 +200,8 @@ subroutine build_model(model, settings, package, error)
write(*,*)'<INFO> COMPILER: ',model%compiler%fc
write(*,*)'<INFO> C COMPILER: ',model%compiler%cc
write(*,*)'<INFO> COMPILER OPTIONS: ', model%fortran_compile_flags
+ write(*,*)'<INFO> C COMPILER OPTIONS: ', model%c_compile_flags
+ write(*,*)'<INFO> LINKER OPTIONS: ', model%link_flags
write(*,*)'<INFO> INCLUDE DIRECTORIES: [', string_cat(model%include_dirs,','),']'
end if
diff --git a/src/fpm_command_line.f90 b/src/fpm_command_line.f90
index c646e4a..df27695 100644
--- a/src/fpm_command_line.f90
+++ b/src/fpm_command_line.f90
@@ -69,8 +69,12 @@ type, extends(fpm_cmd_settings) :: fpm_build_settings
logical :: show_model=.false.
logical :: build_tests=.false.
character(len=:),allocatable :: compiler
+ character(len=:),allocatable :: c_compiler
+ character(len=:),allocatable :: archiver
character(len=:),allocatable :: profile
character(len=:),allocatable :: flag
+ character(len=:),allocatable :: cflag
+ character(len=:),allocatable :: ldflag
end type
type, extends(fpm_build_settings) :: fpm_run_settings
@@ -112,7 +116,53 @@ character(len=20),parameter :: manual(*)=[ character(len=20) ::&
& ' ', 'fpm', 'new', 'build', 'run', &
& 'test', 'runner', 'install', 'update', 'list', 'help', 'version' ]
-character(len=:), allocatable :: val_runner, val_compiler, val_flag, val_profile
+character(len=:), allocatable :: val_runner, val_compiler, val_flag, val_cflag, val_ldflag, &
+ val_profile
+
+character(len=80), parameter :: help_text_compiler(*) = [character(len=80) :: &
+ ' --compiler NAME Specify a compiler name. The default is "gfortran"',&
+ ' unless set by the environment variable FPM_FC.',&
+ ' --c-compiler NAME Specify the C compiler name. By default automatic determined',&
+ ' unless set by the environment variable FPM_CC.',&
+ ' --archiver NAME Specify the archiver name. By default automatic determined',&
+ ' unless set by the environment variable FPM_AR.'&
+ ]
+
+character(len=80), parameter :: help_text_flag(*) = [character(len=80) :: &
+ ' --flag FFLAGS selects compile arguments for the build, the default',&
+ ' value is set by the FPM_FFLAGS environment variable.', &
+ ' These are added to the profile options if --profile', &
+ ' is specified, else these options override the defaults.',&
+ ' Note object and .mod directory locations are always',&
+ ' built in.',&
+ ' --c-flag CFLAGS selects compile arguments specific for C source in the build.',&
+ ' The default value is set by the FPM_CFLAGS environment variable.',&
+ ' --link-flag LDFLAGS',&
+ ' select arguments passed to the linker for the build.',&
+ ' The default value is set by the FPM_LDFLAGS environment variable.'&
+ ]
+
+
+character(len=80), parameter :: help_text_environment(*) = [character(len=80) :: &
+ 'ENVIRONMENT VARIABLES',&
+ ' FPM_FC sets the path to the Fortran compiler used for the build,', &
+ ' will be overwritten by --compiler command line option', &
+ '', &
+ ' FPM_FFLAGS sets the arguments for the Fortran compiler', &
+ ' will be overwritten by --flag command line option', &
+ '', &
+ ' FPM_CC sets the path to the C compiler used for the build,', &
+ ' will be overwritten by --c-compiler command line option', &
+ '', &
+ ' FPM_CFLAGS sets the arguments for the C compiler', &
+ ' will be overwritten by --c-flag command line option', &
+ '', &
+ ' FPM_AR sets the path to the archiver used for the build,', &
+ ' will be overwritten by --archiver command line option', &
+ '', &
+ ' FPM_LDFLAGS sets additional link arguments for creating executables', &
+ ' will be overwritten by --link-flag command line option' &
+ ]
contains
subroutine get_command_line_settings(cmd_settings)
@@ -122,7 +172,12 @@ contains
integer :: i
integer :: widest
type(fpm_install_settings), allocatable :: install_settings
- character(len=:), allocatable :: common_args, working_dir
+ character(len=:), allocatable :: common_args, compiler_args, run_args, working_dir, &
+ & c_compiler, archiver
+
+ character(len=*), parameter :: fc_env = "FC", cc_env = "CC", ar_env = "AR", &
+ & fflags_env = "FFLAGS", cflags_env = "CFLAGS", ldflags_env = "LDFLAGS", &
+ & fc_default = "gfortran", cc_default = " ", ar_default = " ", flags_default = " "
call set_help()
! text for --version switch,
@@ -149,23 +204,32 @@ contains
CLI_RESPONSE_FILE=.true.
cmdarg = get_subcommand()
- common_args = '--directory:C " " '
+ common_args = &
+ ' --directory:C " "' // &
+ ' --verbose F'
+
+ run_args = &
+ ' --target " "' // &
+ ' --list F' // &
+ ' --runner " "'
+
+ compiler_args = &
+ ' --profile " "' // &
+ ' --compiler "'//get_fpm_env(fc_env, fc_default)//'"' // &
+ ' --c-compiler "'//get_fpm_env(cc_env, cc_default)//'"' // &
+ ' --archiver "'//get_fpm_env(ar_env, ar_default)//'"' // &
+ ' --flag:: "'//get_fpm_env(fflags_env, flags_default)//'"' // &
+ ' --c-flag:: "'//get_fpm_env(cflags_env, flags_default)//'"' // &
+ ' --link-flag:: "'//get_fpm_env(ldflags_env, flags_default)//'"'
! now set subcommand-specific help text and process commandline
! arguments. Then call subcommand routine
select case(trim(cmdarg))
case('run')
- call set_args(common_args //'&
- & --target " " &
- & --list F &
+ call set_args(common_args // compiler_args // run_args //'&
& --all F &
- & --profile " "&
& --example F&
- & --runner " " &
- & --compiler "'//get_env('FPM_COMPILER','gfortran')//'" &
- & --flag:: " "&
- & --verbose F&
& --',help_run,version_text)
call check_build_vals()
@@ -193,6 +257,8 @@ contains
if(names(i).eq.'..')names(i)='*'
enddo
+ c_compiler = sget('c-compiler')
+ archiver = sget('archiver')
allocate(fpm_run_settings :: cmd_settings)
val_runner=sget('runner')
if(specified('runner') .and. val_runner.eq.'')val_runner='echo'
@@ -200,7 +266,11 @@ contains
& args=remaining,&
& profile=val_profile,&
& compiler=val_compiler, &
+ & c_compiler=c_compiler, &
+ & archiver=archiver, &
& flag=val_flag, &
+ & cflag=val_cflag, &
+ & ldflag=val_ldflag, &
& example=lget('example'), &
& list=lget('list'),&
& build_tests=.false.,&
@@ -209,23 +279,25 @@ contains
& verbose=lget('verbose') )
case('build')
- call set_args(common_args // '&
- & --profile " " &
+ call set_args(common_args // compiler_args //'&
& --list F &
& --show-model F &
- & --compiler "'//get_env('FPM_COMPILER','gfortran')//'" &
- & --flag:: " "&
& --tests F &
- & --verbose F &
& --',help_build,version_text)
call check_build_vals()
+ c_compiler = sget('c-compiler')
+ archiver = sget('archiver')
allocate( fpm_build_settings :: cmd_settings )
cmd_settings=fpm_build_settings( &
& profile=val_profile,&
& compiler=val_compiler, &
+ & c_compiler=c_compiler, &
+ & archiver=archiver, &
& flag=val_flag, &
+ & cflag=val_cflag, &
+ & ldflag=val_ldflag, &
& list=lget('list'),&
& show_model=lget('show-model'),&
& build_tests=lget('tests'),&
@@ -240,8 +312,7 @@ contains
& --example F &
& --backfill F &
& --full F &
- & --bare F &
- & --verbose:V F',&
+ & --bare F', &
& help_new, version_text)
select case(size(unnamed))
case(1)
@@ -300,9 +371,7 @@ contains
endif
case('help','manual')
- call set_args(common_args // '&
- & --verbose F &
- & ',help_help,version_text)
+ call set_args(common_args, help_help,version_text)
if(size(unnamed).lt.2)then
if(unnamed(1).eq.'help')then
unnamed=[' ', 'fpm']
@@ -348,22 +417,26 @@ contains
call printhelp(help_text)
case('install')
- call set_args(common_args // '&
- & --profile " " --no-rebuild F --verbose F --prefix " " &
+ call set_args(common_args // compiler_args // '&
+ & --no-rebuild F --prefix " " &
& --list F &
- & --compiler "'//get_env('FPM_COMPILER','gfortran')//'" &
- & --flag:: " "&
& --libdir "lib" --bindir "bin" --includedir "include"', &
help_install, version_text)
call check_build_vals()
+ c_compiler = sget('c-compiler')
+ archiver = sget('archiver')
allocate(install_settings)
install_settings = fpm_install_settings(&
list=lget('list'), &
profile=val_profile,&
compiler=val_compiler, &
+ c_compiler=c_compiler, &
+ archiver=archiver, &
flag=val_flag, &
+ cflag=val_cflag, &
+ ldflag=val_ldflag, &
no_rebuild=lget('no-rebuild'), &
verbose=lget('verbose'))
call get_char_arg(install_settings%prefix, 'prefix')
@@ -375,22 +448,14 @@ contains
case('list')
call set_args(common_args // '&
& --list F&
- & --verbose F&
&', help_list, version_text)
call printhelp(help_list_nodash)
if(lget('list'))then
call printhelp(help_list_dash)
endif
case('test')
- call set_args(common_args // '&
- & --target " " &
- & --list F&
- & --profile " "&
- & --runner " " &
- & --compiler "'//get_env('FPM_COMPILER','gfortran')//'" &
- & --flag:: " "&
- & --verbose F&
- & --',help_test,version_text)
+ call set_args(common_args // compiler_args // run_args // ' --', &
+ help_test,version_text)
call check_build_vals()
@@ -411,6 +476,8 @@ contains
if(names(i).eq.'..')names(i)='*'
enddo
+ c_compiler = sget('c-compiler')
+ archiver = sget('archiver')
allocate(fpm_test_settings :: cmd_settings)
val_runner=sget('runner')
if(specified('runner') .and. val_runner.eq.'')val_runner='echo'
@@ -418,7 +485,11 @@ contains
& args=remaining, &
& profile=val_profile, &
& compiler=val_compiler, &
+ & c_compiler=c_compiler, &
+ & archiver=archiver, &
& flag=val_flag, &
+ & cflag=val_cflag, &
+ & ldflag=val_ldflag, &
& example=.false., &
& list=lget('list'), &
& build_tests=.true., &
@@ -427,7 +498,7 @@ contains
& verbose=lget('verbose') )
case('update')
- call set_args(common_args // ' --fetch-only F --verbose F --clean F', &
+ call set_args(common_args // ' --fetch-only F --clean F', &
help_update, version_text)
if( size(unnamed) .gt. 1 )then
@@ -448,7 +519,6 @@ contains
else
call set_args('&
& --list F&
- & --verbose F&
&', help_fpm, version_text)
! Note: will not get here if --version or --usage or --help
! is present on commandline
@@ -485,6 +555,8 @@ contains
endif
val_flag = " " // sget('flag')
+ val_cflag = " " // sget('c-flag')
+ val_ldflag = " " // sget('link-flag')
val_profile = sget('profile')
end subroutine check_build_vals
@@ -665,16 +737,11 @@ contains
' high optimization and "debug" for full debug options.',&
' If --flag is not specified the "debug" flags are the',&
' default. ',&
- ' --flag FFLAGS selects compile arguments for the build. These are',&
- ' added to the profile options if --profile is specified,',&
- ' else these options override the defaults.',&
- ' Note object and .mod directory locations are always',&
- ' built in.',&
+ help_text_compiler, &
+ help_text_flag, &
' --list List candidates instead of building or running them. On ', &
' the fpm(1) command this shows a brief list of subcommands.', &
' --runner CMD Provides a command to prefix program execution paths. ', &
- ' --compiler COMPILER_NAME Compiler name. The environment variable ', &
- ' FPM_COMPILER sets the default. ', &
' -- ARGS Arguments to pass to executables. ', &
' ', &
'VALID FOR ALL SUBCOMMANDS ', &
@@ -713,6 +780,8 @@ contains
' (currently) allow for continued lines or multiple specifications of ', &
' the same option. ', &
' ', &
+ help_text_environment, &
+ ' ', &
'EXAMPLES ', &
' sample commands: ', &
' ', &
@@ -790,14 +859,8 @@ contains
' high optimization and "debug" for full debug options.',&
' If --flag is not specified the "debug" flags are the',&
' default. ',&
- ' --flag FFLAGS selects compile arguments for the build. These are',&
- ' added to the profile options if --profile is specified,',&
- ' else these options override the defaults.',&
- ' Note object and .mod directory locations are always',&
- ' built in.',&
- ' --compiler COMPILER_NAME Specify a compiler name. The default is ', &
- ' "gfortran" unless set by the environment ', &
- ' variable FPM_COMPILER. ', &
+ help_text_compiler, &
+ help_text_flag, &
' --runner CMD A command to prefix the program execution paths with. ', &
' see "fpm help runner" for further details. ', &
' --list list pathname of candidates instead of running them. Note ', &
@@ -806,6 +869,8 @@ contains
' -- ARGS optional arguments to pass to the program(s). The same ', &
' arguments are passed to all program names specified. ', &
' ', &
+ help_text_environment, &
+ ' ', &
'EXAMPLES ', &
' fpm(1) - run or display project applications: ', &
' ', &
@@ -863,20 +928,16 @@ contains
' high optimization and "debug" for full debug options.',&
' If --flag is not specified the "debug" flags are the',&
' default. ',&
- ' --flag FFLAGS selects compile arguments for the build. These are',&
- ' added to the profile options if --profile is specified,',&
- ' else these options override the defaults.',&
- ' Note object and .mod directory locations are always',&
- ' built in.',&
- ' --compiler COMPILER_NAME Specify a compiler name. The default is ', &
- ' "gfortran" unless set by the environment ', &
- ' variable FPM_COMPILER. ', &
+ help_text_compiler, &
+ help_text_flag, &
' --list list candidates instead of building or running them ', &
' --tests build all tests (otherwise only if needed) ', &
' --show-model show the model and exit (do not build) ', &
' --help print this help and exit ', &
' --version print program version information and exit ', &
' ', &
+ help_text_environment, &
+ ' ', &
'EXAMPLES ', &
' Sample commands: ', &
' ', &
@@ -1044,14 +1105,8 @@ contains
' high optimization and "debug" for full debug options.',&
' If --flag is not specified the "debug" flags are the',&
' default. ',&
- ' --flag FFLAGS selects compile arguments for the build. These are',&
- ' added to the profile options if --profile is specified,',&
- ' else these options override the defaults.',&
- ' Note object and .mod directory locations are always',&
- ' built in.',&
- ' --compiler COMPILER_NAME Specify a compiler name. The default is ', &
- ' "gfortran" unless set by the environment ', &
- ' variable FPM_COMPILER. ', &
+ help_text_compiler, &
+ help_text_flag, &
' --runner CMD A command to prefix the program execution paths with. ', &
' see "fpm help runner" for further details. ', &
' --list list candidates instead of building or running them ', &
@@ -1059,6 +1114,8 @@ contains
' The same arguments are passed to all test names ', &
' specified. ', &
' ', &
+ help_text_environment, &
+ ' ', &
'EXAMPLES ', &
'run tests ', &
' ', &
@@ -1116,11 +1173,7 @@ contains
' high optimization and "debug" for full debug options.',&
' If --flag is not specified the "debug" flags are the',&
' default. ',&
- ' --flag FFLAGS selects compile arguments for the build. These are',&
- ' added to the profile options if --profile is specified,',&
- ' else these options override the defaults.',&
- ' Note object and .mod directory locations are always',&
- ' built in.',&
+ help_text_flag, &
' --no-rebuild do not rebuild project before installation', &
' --prefix DIR path to installation directory (requires write access),', &
' the default prefix on Unix systems is $HOME/.local', &
@@ -1132,6 +1185,8 @@ contains
' (default: include)', &
' --verbose print more information', &
'', &
+ help_text_environment, &
+ '', &
'EXAMPLES', &
' 1. Install release version of project:', &
'', &
@@ -1154,4 +1209,17 @@ contains
if (len_trim(var) == 0) deallocate(var)
end subroutine get_char_arg
+
+ !> Get an environment variable for fpm, this routine ensures that every variable
+ !> used by fpm is prefixed with FPM_.
+ function get_fpm_env(env, default) result(val)
+ character(len=*), intent(in) :: env
+ character(len=*), intent(in) :: default
+ character(len=:), allocatable :: val
+
+ character(len=*), parameter :: fpm_prefix = "FPM_"
+
+ val = get_env(fpm_prefix//val, default)
+ end function get_fpm_env
+
end module fpm_command_line
diff --git a/src/fpm_compiler.f90 b/src/fpm_compiler.f90
index c8858b7..34ac941 100644
--- a/src/fpm_compiler.f90
+++ b/src/fpm_compiler.f90
@@ -596,39 +596,62 @@ end function is_unknown
!> Create new compiler instance
-subroutine new_compiler(self, fc)
- !> Fortran compiler name or path
- character(len=*), intent(in) :: fc
+subroutine new_compiler(self, fc, cc)
!> New instance of the compiler
type(compiler_t), intent(out) :: self
-
- character(len=*), parameter :: cc_env = "FPM_C_COMPILER"
+ !> Fortran compiler name or path
+ character(len=*), intent(in) :: fc
+ !> C compiler name or path
+ character(len=*), intent(in) :: cc
self%id = get_compiler_id(fc)
self%fc = fc
- call get_default_c_compiler(self%fc, self%cc)
- self%cc = get_env(cc_env, self%cc)
+ if (len_trim(cc) > 0) then
+ self%cc = cc
+ else
+ call get_default_c_compiler(self%fc, self%cc)
+ end if
end subroutine new_compiler
!> Create new archiver instance
-subroutine new_archiver(self)
+subroutine new_archiver(self, ar)
!> New instance of the archiver
type(archiver_t), intent(out) :: self
+ !> User provided archiver command
+ character(len=*), intent(in) :: ar
+
integer :: estat, os_type
- os_type = get_os_type()
- if (os_type /= OS_WINDOWS .and. os_type /= OS_UNKNOWN) then
- self%ar = "ar -rs "
+ character(len=*), parameter :: arflags = " -rs ", libflags = " /OUT:"
+
+ if (len_trim(ar) > 0) then
+ ! Check first for ar-like commands
+ if (check_compiler(ar, "ar")) then
+ self%ar = ar//arflags
+ end if
+
+ ! Check for lib-like commands
+ if (check_compiler(ar, "lib")) then
+ self%ar = ar//libflags
+ end if
+
+ ! Fallback and assume ar-like behaviour
+ self%ar = ar//arflags
else
+ os_type = get_os_type()
+ if (os_type /= OS_WINDOWS .and. os_type /= OS_UNKNOWN) then
+ self%ar = "ar"//arflags
+ else
call execute_command_line("ar --version > "//get_temp_filename()//" 2>&1", &
- & exitstat=estat)
+ & exitstat=estat)
if (estat /= 0) then
- self%ar = "lib /OUT:"
+ self%ar = "lib"//libflags
else
- self%ar = "ar -rs "
+ self%ar = "ar"//arflags
end if
+ end if
end if
self%use_response_file = os_type == OS_WINDOWS
self%echo = .true.
diff --git a/src/fpm_model.f90 b/src/fpm_model.f90
index dd79b94..38625be 100644
--- a/src/fpm_model.f90
+++ b/src/fpm_model.f90
@@ -124,6 +124,12 @@ type :: fpm_model_t
!> Command line flags passed to fortran for compilation
character(:), allocatable :: fortran_compile_flags
+ !> Command line flags passed to C for compilation
+ character(:), allocatable :: c_compile_flags
+
+ !> Command line flags passed to the linker
+ character(:), allocatable :: link_flags
+
!> Base directory for build
character(:), allocatable :: output_directory
@@ -276,6 +282,8 @@ function info_model(model) result(s)
s = s // ', archiver=(' // debug(model%archiver) // ')'
! character(:), allocatable :: fortran_compile_flags
s = s // ', fortran_compile_flags="' // model%fortran_compile_flags // '"'
+ s = s // ', c_compile_flags="' // model%c_compile_flags // '"'
+ s = s // ', link_flags="' // model%link_flags // '"'
! character(:), allocatable :: output_directory
s = s // ', output_directory="' // model%output_directory // '"'
! type(string_t), allocatable :: link_libraries(:)
diff --git a/src/fpm_targets.f90 b/src/fpm_targets.f90
index f10b330..23f9447 100644
--- a/src/fpm_targets.f90
+++ b/src/fpm_targets.f90
@@ -483,7 +483,7 @@ subroutine resolve_target_linking(targets, model)
if (target%target_type /= FPM_TARGET_C_OBJECT) then
target%compile_flags = model%fortran_compile_flags//" "//global_include_flags
else
- target%compile_flags = global_include_flags
+ target%compile_flags = model%c_compile_flags//" "//global_include_flags
end if
allocate(target%link_objects(0))
@@ -498,7 +498,7 @@ subroutine resolve_target_linking(targets, model)
call get_link_objects(target%link_objects,target,is_exe=.true.)
- target%link_flags = string_cat(target%link_objects," ")
+ target%link_flags = model%link_flags//" "//string_cat(target%link_objects," ")
if (allocated(target%link_libraries)) then
if (size(target%link_libraries) > 0) then