aboutsummaryrefslogtreecommitdiff
path: root/src/fpm_command_line.f90
diff options
context:
space:
mode:
authorSebastian Ehlert <28669218+awvwgk@users.noreply.github.com>2021-07-30 19:59:26 +0200
committerSebastian Ehlert <28669218+awvwgk@users.noreply.github.com>2021-07-30 23:41:34 +0200
commitc6f0ec64b8060523beaf828ceae32fa3827f65fb (patch)
tree0aeb9c87496fd09e8d6b9596cacd5355d53c10ee /src/fpm_command_line.f90
parent5d22f5aac698c4b8f135a226e944be9ded9475b0 (diff)
downloadfpm-c6f0ec64b8060523beaf828ceae32fa3827f65fb.tar.gz
fpm-c6f0ec64b8060523beaf828ceae32fa3827f65fb.zip
Move default flags fetching and build name generation to model
Diffstat (limited to 'src/fpm_command_line.f90')
-rw-r--r--src/fpm_command_line.f9019
1 files changed, 1 insertions, 18 deletions
diff --git a/src/fpm_command_line.f90 b/src/fpm_command_line.f90
index 86e6d5d..90d7198 100644
--- a/src/fpm_command_line.f90
+++ b/src/fpm_command_line.f90
@@ -31,7 +31,6 @@ use M_CLI2, only : get_subcommand, CLI_RESPONSE_FILE
use fpm_strings, only : lower, split, fnv_1a, to_fortran_name, is_fortran_name
use fpm_filesystem, only : basename, canon_path, which
use fpm_environment, only : run, get_command_arguments_quoted
-use fpm_compiler, only : get_default_compile_flags
use fpm_error, only : fpm_stop
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, &
& stdout=>output_unit, &
@@ -70,7 +69,6 @@ type, extends(fpm_cmd_settings) :: fpm_build_settings
logical :: show_model=.false.
character(len=:),allocatable :: compiler
character(len=:),allocatable :: profile
- character(len=:),allocatable :: build_name
character(len=:),allocatable :: flag
end type
@@ -113,7 +111,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, val_profile
+character(len=:), allocatable :: val_runner, val_compiler, val_flag, val_profile
contains
subroutine get_command_line_settings(cmd_settings)
@@ -199,7 +197,6 @@ contains
if(specified('runner') .and. val_runner.eq.'')val_runner='echo'
cmd_settings=fpm_run_settings(&
& args=remaining,&
- & build_name=val_build,&
& profile=val_profile,&
& compiler=val_compiler, &
& flag=val_flag, &
@@ -223,7 +220,6 @@ 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, &
@@ -361,7 +357,6 @@ contains
allocate(install_settings)
install_settings = fpm_install_settings(&
list=lget('list'), &
- build_name=val_build, &
profile=val_profile,&
compiler=val_compiler, &
flag=val_flag, &
@@ -417,7 +412,6 @@ contains
if(specified('runner') .and. val_runner.eq.'')val_runner='echo'
cmd_settings=fpm_test_settings(&
& args=remaining, &
- & build_name=val_build, &
& profile=val_profile, &
& compiler=val_compiler, &
& flag=val_flag, &
@@ -487,17 +481,6 @@ contains
val_flag = " " // sget('flag')
val_profile = sget('profile')
- if (val_flag == '') then
- call get_default_compile_flags(val_compiler, val_profile == "release", val_flag)
- else
- 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)
end subroutine check_build_vals