aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorSebastian Ehlert <28669218+awvwgk@users.noreply.github.com>2021-03-17 22:20:25 +0100
committerSebastian Ehlert <28669218+awvwgk@users.noreply.github.com>2021-03-18 09:23:22 +0100
commitbfbd2db2a331469c960b423e013e0dd9212286c5 (patch)
tree4cf57252cbc6e37ccd9fcb32f9b47d00d8c6dc22
parentb4a266f52cbc1414b11f9ce0492301c244f0b6a8 (diff)
downloadfpm-bfbd2db2a331469c960b423e013e0dd9212286c5.tar.gz
fpm-bfbd2db2a331469c960b423e013e0dd9212286c5.zip
Introduce compilation profiles
- default is equal to debug unless --flag is present and overwrites all arguments - debug is the developement profile, options given by --flag are appended - release is the production profile, options given by --flag are appended
-rw-r--r--fpm/src/fpm_command_line.f9087
-rw-r--r--fpm/test/cli_test/cli_test.f9036
2 files changed, 67 insertions, 56 deletions
diff --git a/fpm/src/fpm_command_line.f90 b/fpm/src/fpm_command_line.f90
index 65812b8..4f38204 100644
--- a/fpm/src/fpm_command_line.f90
+++ b/fpm/src/fpm_command_line.f90
@@ -65,6 +65,7 @@ type, extends(fpm_cmd_settings) :: fpm_build_settings
logical :: list=.false.
logical :: show_model=.false.
character(len=:),allocatable :: compiler
+ character(len=:),allocatable :: profile
character(len=:),allocatable :: build_name
character(len=:),allocatable :: flag
end type
@@ -108,7 +109,7 @@ 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_build, val_compiler, val_flag
+character(len=:), allocatable :: val_runner, val_build, val_compiler, val_flag, val_profile
contains
subroutine get_command_line_settings(cmd_settings)
@@ -155,7 +156,7 @@ contains
& --target " " &
& --list F &
& --all F &
- & --release F&
+ & --profile "default"&
& --example F&
& --runner " " &
& --compiler "'//get_env('FPM_COMPILER','gfortran')//'" &
@@ -194,6 +195,7 @@ contains
cmd_settings=fpm_run_settings(&
& args=remaining,&
& build_name=val_build,&
+ & profile=val_profile,&
& compiler=val_compiler, &
& flag=val_flag, &
& example=lget('example'), &
@@ -204,7 +206,7 @@ contains
case('build')
call set_args( '&
- & --release F &
+ & --profile "default" &
& --list F &
& --show-model F &
& --compiler "'//get_env('FPM_COMPILER','gfortran')//'" &
@@ -217,6 +219,7 @@ contains
allocate( fpm_build_settings :: cmd_settings )
cmd_settings=fpm_build_settings( &
& build_name=val_build,&
+ & profile=val_profile,&
& compiler=val_compiler, &
& flag=val_flag, &
& list=lget('list'),&
@@ -342,7 +345,7 @@ contains
call printhelp(help_text)
case('install')
- call set_args('--release F --no-rebuild F --verbose F --prefix " " &
+ call set_args('--profile "default" --no-rebuild F --verbose F --prefix " " &
& --list F &
& --compiler "'//get_env('FPM_COMPILER','gfortran')//'" &
& --flag:: " "&
@@ -355,6 +358,7 @@ contains
install_settings = fpm_install_settings(&
list=lget('list'), &
build_name=val_build, &
+ profile=val_profile,&
compiler=val_compiler, &
flag=val_flag, &
no_rebuild=lget('no-rebuild'), &
@@ -378,7 +382,7 @@ contains
call set_args('&
& --target " " &
& --list F&
- & --release F&
+ & --profile "default"&
& --runner " " &
& --compiler "'//get_env('FPM_COMPILER','gfortran')//'" &
& --flag:: " "&
@@ -410,6 +414,7 @@ contains
cmd_settings=fpm_test_settings(&
& args=remaining, &
& build_name=val_build, &
+ & profile=val_profile, &
& compiler=val_compiler, &
& flag=val_flag, &
& example=.false., &
@@ -459,6 +464,7 @@ contains
contains
subroutine check_build_vals()
+ character(len=:), allocatable :: flags
val_compiler=sget('compiler')
if(val_compiler.eq.'') then
@@ -466,13 +472,15 @@ contains
endif
val_flag = sget('flag')
+ val_profile = sget('profile')
if (val_flag == '') then
- call get_default_compile_flags(val_compiler, lget('release'), val_flag)
+ call get_default_compile_flags(val_compiler, val_profile == "release", val_flag)
else
- if (lget('release')) then
- write(stdout,'(a)') &
- '<WARNING> --release ignored since explicit --flag argument provided'
- end if
+ select case(val_profile)
+ case("release", "debug")
+ call get_default_compile_flags(val_compiler, val_profile == "release", flags)
+ val_flag = flags // " " // val_flag
+ end select
end if
allocate(character(len=16) :: val_build)
write(val_build, '(z16.16)') fnv_1a(val_flag)
@@ -536,17 +544,17 @@ contains
' ']
help_list_dash = [character(len=80) :: &
' ', &
- ' build [--compiler COMPILER_NAME] [--release] [--flag FFLAGS] [--list] ', &
+ ' build [--compiler COMPILER_NAME] [--profile PROF] [--flag FFLAGS] [--list] ', &
' help [NAME(s)] ', &
' new NAME [[--lib|--src] [--app] [--test] [--example]]| ', &
' [--full|--bare][--backfill] ', &
' update [NAME(s)] [--fetch-only] [--clean] [--verbose] ', &
' list [--list] ', &
- ' run [[--target] NAME(s) [--example] [--release] [--flag FFLAGS] [--all] ', &
+ ' run [[--target] NAME(s) [--example] [--profile PROF] [--flag FFLAGS] [--all] ', &
' [--runner "CMD"] [--compiler COMPILER_NAME] [--list] [-- ARGS] ', &
- ' test [[--target] NAME(s)] [--release] [--flag FFLAGS] [--runner "CMD"] [--list]', &
+ ' test [[--target] NAME(s)] [--profile PROF] [--flag FFLAGS] [--runner "CMD"] [--list]', &
' [--compiler COMPILER_NAME] [-- ARGS] ', &
- ' install [--release] [--flag FFLAGS] [--no-rebuild] [--prefix PATH] [options] ', &
+ ' install [--profile PROF] [--flag FFLAGS] [--no-rebuild] [--prefix PATH] [options] ', &
' ']
help_usage=[character(len=80) :: &
'' ]
@@ -612,7 +620,7 @@ contains
' ', &
' # bash(1) alias example: ', &
' alias fpm-install=\ ', &
- ' "fpm run --release --runner ''install -vbp -m 0711 -t ~/.local/bin''" ', &
+ ' "fpm run --profile release --runner ''install -vbp -m 0711 -t ~/.local/bin''" ', &
' fpm-install ', &
'' ]
help_fpm=[character(len=80) :: &
@@ -652,25 +660,26 @@ contains
' ', &
' Their syntax is ', &
' ', &
- ' build [--release] [--flag FFLAGS] [--list] [--compiler COMPILER_NAME]', &
+ ' build [--profile PROF] [--flag FFLAGS] [--list] [--compiler COMPILER_NAME]', &
' new NAME [[--lib|--src] [--app] [--test] [--example]]| ', &
' [--full|--bare][--backfill] ', &
' update [NAME(s)] [--fetch-only] [--clean] ', &
- ' run [[--target] NAME(s)] [--release] [--flag FFLAGS] [--list] [--example]', &
+ ' run [[--target] NAME(s)] [--profile PROF] [--flag FFLAGS] [--list] [--example]', &
' [--all] [--runner "CMD"] [--compiler COMPILER_NAME] [-- ARGS] ', &
- ' test [[--target] NAME(s)] [--release] [--flag FFLAGS] [--list] ', &
+ ' test [[--target] NAME(s)] [--profile PROF] [--flag FFLAGS] [--list] ', &
' [--runner "CMD"] [--compiler COMPILER_NAME] [-- ARGS] ', &
' help [NAME(s)] ', &
' list [--list] ', &
- ' install [--release] [--flag FFLAGS] [--no-rebuild] [--prefix PATH] [options]', &
+ ' install [--profile PROF] [--flag FFLAGS] [--no-rebuild] [--prefix PATH] [options]', &
' ', &
'SUBCOMMAND OPTIONS ', &
- ' --release Builds or runs in release mode (versus debug mode). fpm(1)', &
- ' Defaults to using common compiler debug flags. ', &
- ' When this flag is present common compiler optimization flags', &
- ' are used.', &
+ ' --profile PROF Builds or runs with the given profile (either release or debug).', &
+ ' fpm(1) defaults to using common compiler debug flags with debug', &
+ ' profile, common compiler optimization flags are used with the', &
+ ' release profile', &
' --flag FFLAGS Use compile arguments provided in FFLAGS rather than', &
- ' defaults from debug or release mode, module flags are', &
+ ' defaults, if a profile (debug or release) is present the', &
+ ' FFLAGS are appended rather than replaced, module flags are', &
' provided by fpm(1) and must not be present in FFLAGS', &
' --list List candidates instead of building or running them. On ', &
' the fpm(1) command this shows a brief list of subcommands.', &
@@ -693,7 +702,7 @@ contains
' fpm run ', &
' fpm run --example ', &
' fpm new --help ', &
- ' fpm run myprogram --release -- -x 10 -y 20 --title "my title" ', &
+ ' fpm run myprogram --profile release -- -x 10 -y 20 --title "my title"', &
' fpm install --prefix ~/.local ', &
' ', &
'SEE ALSO ', &
@@ -730,7 +739,7 @@ contains
' run(1) - the fpm(1) subcommand to run project applications ', &
' ', &
'SYNOPSIS ', &
- ' fpm run [[--target] NAME(s) [--release] [--flag FFLAGS]', &
+ ' fpm run [[--target] NAME(s) [--profile PROF] [--flag FFLAGS]', &
' [--compiler COMPILER_NAME] [--runner "CMD"] [--example]', &
' [--list] [--all] [-- ARGS]', &
' ', &
@@ -756,7 +765,7 @@ contains
' the special characters from shell expansion. ', &
' --all Run all examples or applications. An alias for --target ''*''. ', &
' --example Run example programs instead of applications. ', &
- ' --release selects the optimized build instead of the debug build. ', &
+ ' --profile PROF Selects the compilation profile for the build. ', &
' --flags FFLAGS selects compile arguments for the build', &
' --compiler COMPILER_NAME Specify a compiler name. The default is ', &
' "gfortran" unless set by the environment ', &
@@ -788,7 +797,7 @@ contains
' fpm run myprog -- -x 10 -y 20 --title "my title line" ', &
' ', &
' # run production version of two applications ', &
- ' fpm run --target prg1,prg2 --release ', &
+ ' fpm run --target prg1,prg2 --profile release ', &
' ', &
' # install executables in directory (assuming install(1) exists) ', &
' fpm run --runner ''install -b -m 0711 -p -t /usr/local/bin'' ', &
@@ -798,7 +807,7 @@ contains
' build(1) - the fpm(1) subcommand to build a project ', &
' ', &
'SYNOPSIS ', &
- ' fpm build [--release] [--flags FFLAGS] [--compiler COMPILER_NAME] [-list]', &
+ ' fpm build [--profile PROF] [--flags FFLAGS] [--compiler COMPILER_NAME] [-list]', &
' ', &
' fpm build --help|--version ', &
' ', &
@@ -820,7 +829,7 @@ contains
' specified in the "fpm.toml" file. ', &
' ', &
'OPTIONS ', &
- ' --release build in build/*_release instead of build/*_debug with ', &
+ ' --profile PROF selects the compilation profile for the build ', &
' high optimization instead of full debug options. ', &
' --flags FFLAGS selects compile arguments for the build', &
' --compiler COMPILER_NAME Specify a compiler name. The default is ', &
@@ -834,8 +843,8 @@ contains
'EXAMPLES ', &
' Sample commands: ', &
' ', &
- ' fpm build # build with debug options ', &
- ' fpm build --release # build with high optimization ', &
+ ' fpm build # build with debug options ', &
+ ' fpm build --profile release # build with high optimization ', &
'' ]
help_help=[character(len=80) :: &
@@ -979,7 +988,7 @@ contains
' test(1) - the fpm(1) subcommand to run project tests ', &
' ', &
'SYNOPSIS ', &
- ' fpm test [[--target] NAME(s)] [--release] [--flag FFLAGS]', &
+ ' fpm test [[--target] NAME(s)] [--profile PROF] [--flag FFLAGS]', &
' [--compiler COMPILER_NAME ] [--runner "CMD"] [--list][-- ARGS]', &
' ', &
' fpm test --help|--version ', &
@@ -996,7 +1005,7 @@ contains
' any single character and "*" represents any string. ', &
' Note The glob string normally needs quoted to ', &
' protect the special characters from shell expansion.', &
- ' --release selects the optimized build instead of the debug build. ', &
+ ' --profile PROF selects the compilation profile for the build.', &
' --flags FFLAGS selects compile arguments for the build', &
' --compiler COMPILER_NAME Specify a compiler name. The default is ', &
' "gfortran" unless set by the environment ', &
@@ -1020,7 +1029,7 @@ contains
' # run a specific test and pass arguments to the command ', &
' fpm test mytest -- -x 10 -y 20 --title "my title line" ', &
' ', &
- ' fpm test tst1 tst2 --release # run production version of two tests ', &
+ ' fpm test tst1 tst2 --profile PROF # run production version of two tests', &
'' ]
help_update=[character(len=80) :: &
'NAME', &
@@ -1046,8 +1055,8 @@ contains
' install(1) - install fpm projects', &
'', &
'SYNOPSIS', &
- ' fpm install [--release] [--flag FFLAGS] [--list] [--no-rebuild] [--prefix DIR]', &
- ' [--bindir DIR] [--libdir DIR] [--includedir DIR]', &
+ ' fpm install [--profile PROF] [--flag FFLAGS] [--list] [--no-rebuild]', &
+ ' [--prefix DIR] [--bindir DIR] [--libdir DIR] [--includedir DIR]', &
' [--verbose]', &
'', &
'DESCRIPTION', &
@@ -1060,7 +1069,7 @@ contains
'OPTIONS', &
' --list list all installable targets for this project,', &
' but do not install any of them', &
- ' --release selects the optimized build instead of the debug build', &
+ ' --profile selects the compilation profile for installation', &
' --flags FFLAGS selects compile arguments for the build', &
' --no-rebuild do not rebuild project before installation', &
' --prefix DIR path to installation directory (requires write access),', &
@@ -1076,7 +1085,7 @@ contains
'EXAMPLES', &
' 1. Install release version of project:', &
'', &
- ' fpm install --release', &
+ ' fpm install --profile release', &
'', &
' 2. Install the project without rebuilding the executables:', &
'', &
diff --git a/fpm/test/cli_test/cli_test.f90 b/fpm/test/cli_test/cli_test.f90
index c30d688..80e4526 100644
--- a/fpm/test/cli_test/cli_test.f90
+++ b/fpm/test/cli_test/cli_test.f90
@@ -28,9 +28,9 @@ integer :: i, ios
logical :: w_e,act_w_e ; namelist/act_cli/act_w_e
logical :: w_t,act_w_t ; namelist/act_cli/act_w_t
-character(len=63) :: build_name,act_build_name ; namelist/act_cli/act_build_name
+character(len=63) :: profile,act_profile ; namelist/act_cli/act_profile
character(len=:),allocatable :: args,act_args ; namelist/act_cli/act_args
-namelist/expected/cmd,cstat,estat,w_e,w_t,name,build_name,args
+namelist/expected/cmd,cstat,estat,w_e,w_t,name,profile,args
integer :: lun
logical,allocatable :: tally(:)
logical,allocatable :: subtally(:)
@@ -50,19 +50,21 @@ character(len=*),parameter :: tests(*)= [ character(len=256) :: &
'CMD="run", ', &
'CMD="run my_project", NAME="my_project", ', &
'CMD="run proj1 p2 project3", NAME="proj1","p2","project3", ', &
-'CMD="run proj1 p2 project3 --release", NAME="proj1","p2","project3",build_name="release",', &
-'CMD="run proj1 p2 project3 --release -- arg1 -x ""and a long one""", &
- &NAME="proj1","p2","project3",build_name="release",ARGS="""arg1"" -x ""and a long one""", ', &
+'CMD="run proj1 p2 project3 --profile debug", NAME="proj1","p2","project3",profile="debug",', &
+'CMD="run proj1 p2 project3 --profile release", NAME="proj1","p2","project3",profile="release",', &
+'CMD="run proj1 p2 project3 --profile release -- arg1 -x ""and a long one""", &
+ &NAME="proj1","p2","project3",profile="release",ARGS="""arg1"" -x ""and a long one""", ', &
'CMD="test", ', &
'CMD="test my_project", NAME="my_project", ', &
'CMD="test proj1 p2 project3", NAME="proj1","p2","project3", ', &
-'CMD="test proj1 p2 project3 --release", NAME="proj1","p2","project3",build_name="release",', &
-'CMD="test proj1 p2 project3 --release -- arg1 -x ""and a long one""", &
- &NAME="proj1","p2","project3",build_name="release" ARGS="""arg1"" -x ""and a long one""", ', &
+'CMD="test proj1 p2 project3 --profile debug", NAME="proj1","p2","project3",profile="debug",', &
+'CMD="test proj1 p2 project3 --profile release", NAME="proj1","p2","project3",profile="release",', &
+'CMD="test proj1 p2 project3 --profile release -- arg1 -x ""and a long one""", &
+ &NAME="proj1","p2","project3",profile="release" ARGS="""arg1"" -x ""and a long one""", ', &
-'CMD="build", NAME= build_name="debug",ARGS="",', &
-'CMD="build --release", NAME= build_name="release",ARGS="",', &
+'CMD="build", NAME= profile="default",ARGS="",', &
+'CMD="build --profile release", NAME= profile="release",ARGS="",', &
' ' ]
character(len=256) :: readme(3)
@@ -90,7 +92,7 @@ if(command_argument_count().eq.0)then ! assume if called with no arguments to d
endif
! blank out name group EXPECTED
name=[(repeat(' ',len(name)),i=1,max_names)] ! the words on the command line sans the subcommand name
- build_name="debug" ! --release
+ profile="default" ! --profile PROF
w_e=.false. ! --app
w_t=.false. ! --test
args=repeat(' ',132) ! -- ARGS
@@ -107,7 +109,7 @@ if(command_argument_count().eq.0)then ! assume if called with no arguments to d
if(estat.eq.0)then
open(file='_test_cli',newunit=lun,delim='quote')
act_name=[(repeat(' ',len(act_name)),i=1,max_names)]
- act_build_name='debug'
+ act_profile='default'
act_w_e=.false.
act_w_t=.false.
act_args=repeat(' ',132)
@@ -119,7 +121,7 @@ if(command_argument_count().eq.0)then ! assume if called with no arguments to d
! compare results to expected values
subtally=[logical ::]
call test_test('NAME',all(act_name.eq.name))
- call test_test('RELEASE',act_build_name.eq.build_name)
+ call test_test('PROFILE',act_profile.eq.profile)
call test_test('WITH_EXPECTED',act_w_e.eqv.w_e)
call test_test('WITH_TESTED',act_w_t.eqv.w_t)
call test_test('WITH_TEST',act_w_t.eqv.w_t)
@@ -204,7 +206,7 @@ allocate (character(len=len(name)) :: act_name(0) )
act_args=''
act_w_e=.false.
act_w_t=.false.
-act_build_name='debug'
+act_profile='default'
select type(settings=>cmd_settings)
type is (fpm_new_settings)
@@ -212,13 +214,13 @@ type is (fpm_new_settings)
act_w_t=settings%with_test
act_name=[trim(settings%name)]
type is (fpm_build_settings)
- act_build_name=settings%build_name
+ act_profile=settings%profile
type is (fpm_run_settings)
- act_build_name=settings%build_name
+ act_profile=settings%profile
act_name=settings%name
act_args=settings%args
type is (fpm_test_settings)
- act_build_name=settings%build_name
+ act_profile=settings%profile
act_name=settings%name
act_args=settings%args
type is (fpm_install_settings)