aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--fpm/fpm.toml2
-rw-r--r--fpm/src/fpm.f90228
-rw-r--r--fpm/src/fpm/error.f908
-rw-r--r--fpm/src/fpm/git.f904
-rw-r--r--fpm/src/fpm/manifest/package.f904
-rw-r--r--fpm/src/fpm_backend.f9018
-rw-r--r--fpm/src/fpm_command_line.f90240
-rw-r--r--fpm/src/fpm_environment.f9034
-rw-r--r--fpm/src/fpm_filesystem.f9044
-rw-r--r--fpm/src/fpm_model.f902
-rw-r--r--fpm/src/fpm_sources.f9024
-rw-r--r--fpm/src/fpm_strings.f908
-rw-r--r--fpm/src/fpm_targets.f9032
-rw-r--r--fpm/test/cli_test/cli_test.f9030
14 files changed, 524 insertions, 154 deletions
diff --git a/fpm/fpm.toml b/fpm/fpm.toml
index 7afc0a0..fa91f2f 100644
--- a/fpm/fpm.toml
+++ b/fpm/fpm.toml
@@ -12,7 +12,7 @@ tag = "v0.2.1"
[dependencies.M_CLI2]
git = "https://github.com/urbanjost/M_CLI2.git"
-rev = "893cac0ce374bf07a70ffb9556439c7390e58131"
+rev = "598e44164eee383b8a0775aa75b7d1bb100481c3"
[[test]]
name = "cli-test"
diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90
index 5e190c8..07bf483 100644
--- a/fpm/src/fpm.f90
+++ b/fpm/src/fpm.f90
@@ -25,7 +25,6 @@ public :: cmd_build, cmd_install, cmd_run
contains
-
recursive subroutine add_libsources_from_package(sources,link_libraries,package_list,package, &
package_root,dev_depends,error)
! Discover library sources in a package, recursively including dependencies
@@ -152,9 +151,15 @@ subroutine build_model(model, settings, package, error)
type(fpm_build_settings), intent(in) :: settings
type(package_config_t), intent(in) :: package
type(error_t), allocatable, intent(out) :: error
+ type(string_t), allocatable :: package_list(:)
integer :: i
- type(string_t), allocatable :: package_list(:)
+ character(len=:),allocatable :: module_path_switch
+
+ if(settings%verbose)then
+ write(*,*)'<INFO>BUILD_NAME:',settings%build_name
+ write(*,*)'<INFO>COMPILER: ',settings%compiler
+ endif
model%package_name = package%name
if (allocated(package%build%link)) then
@@ -166,25 +171,206 @@ subroutine build_model(model, settings, package, error)
allocate(package_list(1))
package_list(1)%s = package%name
- ! #TODO: Choose flags and output directory based on cli settings & manifest inputs
- model%fortran_compiler = 'gfortran'
-
- if(settings%release)then
- model%output_directory = 'build/gfortran_release'
- model%fortran_compile_flags=' &
- & -O3 &
- & -Wimplicit-interface &
- & -fPIC &
- & -fmax-errors=1 &
- & -ffast-math &
- & -funroll-loops ' // &
- & '-J'//join_path(model%output_directory,model%package_name)
- else
- model%output_directory = 'build/gfortran_debug'
- model%fortran_compile_flags = ' -Wall -Wextra -Wimplicit-interface -fPIC -fmax-errors=1 -g '// &
- '-fbounds-check -fcheck-array-temporaries -fbacktrace '// &
- '-J'//join_path(model%output_directory,model%package_name)
- endif
+ model%fortran_compiler=settings%compiler
+
+ model%output_directory = join_path('build',model%fortran_compiler//'_'//settings%build_name)
+
+ if(settings%compiler.eq.'')then
+ model%fortran_compiler = 'gfortran'
+ else
+ model%fortran_compiler = settings%compiler
+ endif
+
+! #TODO: Choose flags and output directory based on cli settings & manifest inputs
+! special reserved names "debug" and "release" are for supported compilers with no user-specified compile or load flags
+
+! vendor Fortran C Module output Module include OpenMP Free for OSS
+! compiler compiler directory directory
+! Gnu gfortran gcc -J -I -fopenmp X
+! Intel ifort icc -module -I -qopenmp X
+! Intel(Windows) ifort icc /module:path /I /Qopenmp X
+! Intel oneAPI ifx icx -module -I -qopenmp X
+! PGI pgfortran pgcc -module -I -mp X
+! NVIDIA nvfortran nvc -module -I -mp X
+! LLVM flang flang clang -module -I -mp X
+! LFortran lfortran --- ? ? ? X
+! Lahey/Futjitsu lfc ? -M -I -openmp ?
+! NAG nagfor ? -mdir -I -openmp x
+! Cray crayftn craycc -J -I -homp ?
+! IBM xlf90 ? -qmoddir -I -qsmp X
+! Oracle/Sun ? ? -moddir= -M -xopenmp ?
+! Silverfrost FTN95 ftn95 ? ? /MOD_PATH ? ?
+! Elbrus ? lcc -J -I -fopenmp ?
+! Hewlett Packard ? ? ? ? ? discontinued
+! Watcom ? ? ? ? ? discontinued
+! PathScale ? ? -module -I -mp discontinued
+! G95 ? ? -fmod= -I -fopenmp discontinued
+! Open64 ? ? -module -I -mp discontinued
+! Unisys ? ? ? ? ? discontinued
+
+ select case(settings%build_name//'_'//settings%compiler)
+
+ case('release_gfortran') ! -J
+ model%fortran_compile_flags=' &
+ & -O3&
+ & -Wimplicit-interface&
+ & -fPIC&
+ & -fmax-errors=1&
+ & -ffast-math&
+ & -funroll-loops&
+ & '
+ case('debug_gfortran')
+ model%fortran_compile_flags = '&
+ & -Wall &
+ & -Wextra &
+ &-Wimplicit-interface &
+ &-fPIC -fmax-errors=1 &
+ &-g &
+ &-fbounds-check &
+ &-fcheck-array-temporaries &
+ &-fbacktrace '
+
+ case('release_f95') ! -J
+ model%fortran_compile_flags=' &
+ & -O3&
+ & -Wimplicit-interface&
+ & -fPIC&
+ & -std=f95 &
+ & -fmax-errors=1&
+ & -ffast-math&
+ & -funroll-loops&
+ & '
+ case('debug_f95')
+ model%fortran_compile_flags = '&
+ & -Wall &
+ & -Wextra &
+ &-Wimplicit-interface &
+ &-fPIC -fmax-errors=1 &
+ &-g &
+ &-std=f95 &
+ &-fbounds-check &
+ &-fcheck-array-temporaries &
+ &-fbacktrace '
+
+ case('release_gnu') ! -J
+ model%fortran_compile_flags=' &
+ & -O3&
+ & -Wimplicit-interface&
+ & -fPIC&
+ & -fmax-errors=1&
+ & -ffast-math&
+ & -funroll-loops&
+ & -std=f2018 &
+ & -Wno-maybe-uninitialized -Wno-uninitialized &
+ & '
+ model%fortran_compiler = 'gfortran'
+ case('debug_gnu')
+ model%fortran_compile_flags = '&
+ & -Wall &
+ & -Wextra &
+ & -Wimplicit-interface &
+ & -fPIC -fmax-errors=1 &
+ & -g &
+ & -fbounds-check &
+ & -fcheck-array-temporaries &
+ & -std=f2018 &
+ & -Wno-maybe-uninitialized -Wno-uninitialized &
+ & -fbacktrace '
+ model%fortran_compiler = 'gfortran'
+
+ case('release_nvfortran')
+ model%fortran_compile_flags = ' &
+ & -Mbackslash&
+ & '
+ case('debug_nvfortran')
+ model%fortran_compile_flags = '&
+ & -Minform=inform &
+ & -Mbackslash &
+ & -traceback&
+ & '
+
+ case('release_ifort')
+ model%fortran_compile_flags = ' &
+ & -fp-model precise &
+ & -pc 64 &
+ & -align all &
+ & -error-limit 1 &
+ & -reentrancy threaded &
+ & -nogen-interfaces &
+ & -assume byterecl &
+ & -assume nounderscore'
+ case('debug_ifort')
+ model%fortran_compile_flags = '&
+ & -warn all &
+ & -check all &
+ & -error-limit 1 &
+ & -O0 &
+ & -g &
+ & -assume byterecl &
+ & -traceback '
+ case('release_ifx')
+ model%fortran_compile_flags = ' '
+ case('debug_ifx')
+ model%fortran_compile_flags = ' '
+
+ case('release_pgfortran','release_pgf90','release_pgf95') ! Portland Group F90/F95 compilers
+ model%fortran_compile_flags = ' '
+ case('debug_pgfortran','debug_pgf90','debug_pgf95') ! Portland Group F90/F95 compilers
+ model%fortran_compile_flags = ' '
+
+ case('release_flang')
+ model%fortran_compile_flags = ' '
+ case('debug_flang')
+ model%fortran_compile_flags = ' '
+
+ case('release_lfc')
+ model%fortran_compile_flags = ' '
+ case('debug_lfc')
+ model%fortran_compile_flags = ' '
+
+ case('release_nagfor')
+ model%fortran_compile_flags = ' '
+ case('debug_nagfor')
+ model%fortran_compile_flags = ' '
+
+ case('release_crayftn')
+ model%fortran_compile_flags = ' '
+ case('debug_crayftn')
+ model%fortran_compile_flags = ' '
+
+ case('release_xlf90')
+ model%fortran_compile_flags = ' '
+ case('debug_xlf90')
+ model%fortran_compile_flags = ' '
+
+ case default
+ model%fortran_compile_flags = ' '
+ write(*,*)'<WARNING> unknown compiler (',settings%compiler,')'
+ write(*,*)' and build name (',settings%build_name,')'
+ write(*,*)' combination.'
+ write(*,*)' known compilers are gfortran, nvfortran, ifort'
+ end select
+
+ select case(settings%compiler)
+ case('gfortran') ; module_path_switch=' -J '
+ case('gnu') ; module_path_switch=' -J '
+ case('nvfortran') ; module_path_switch=' -module '
+ case('ifort') ; module_path_switch=' -module '
+ case('ifx') ; module_path_switch=' -module '
+ case('pgfortran') ; module_path_switch=' -module '
+ case('flang') ; module_path_switch=' -module '
+ case('lfc') ; module_path_switch=' -M '
+ case('crayftn') ; module_path_switch=' -J '
+ case('nagfor') ; module_path_switch=' -mdir '
+ case('xlf90') ; module_path_switch=' -qmoddir '
+ case default
+ module_path_switch=' -module '
+ write(*,*)'UNKNOWN COMPILER NAME ',settings%compiler
+ end select
+
+ model%fortran_compile_flags = model%fortran_compile_flags//' '//&
+ & module_path_switch//join_path(model%output_directory,model%package_name)
+
model%link_flags = ''
! Add sources from executable directories
diff --git a/fpm/src/fpm/error.f90 b/fpm/src/fpm/error.f90
index e69ff1e..2cfd964 100644
--- a/fpm/src/fpm/error.f90
+++ b/fpm/src/fpm/error.f90
@@ -82,9 +82,9 @@ contains
allocate(error)
error%message = 'Parse error: '//message//new_line('a')
-
+
error%message = error%message//file_name
-
+
if (present(line_num)) then
write(temp_string,'(I0)') line_num
@@ -115,9 +115,9 @@ contains
error%message = error%message//new_line('a')
error%message = error%message//' | '//repeat(' ',line_col-1)//'^'
-
+
end if
-
+
end if
end if
diff --git a/fpm/src/fpm/git.f90 b/fpm/src/fpm/git.f90
index 187b551..af4ae22 100644
--- a/fpm/src/fpm/git.f90
+++ b/fpm/src/fpm/git.f90
@@ -138,7 +138,7 @@ contains
!> Error
type(error_t), allocatable, intent(out) :: error
-
+
!> git object ref
character(:), allocatable :: object
@@ -173,7 +173,7 @@ contains
return
end if
- end subroutine checkout
+ end subroutine checkout
!> Show information on git target
diff --git a/fpm/src/fpm/manifest/package.f90 b/fpm/src/fpm/manifest/package.f90
index 64b0f82..7f2f91e 100644
--- a/fpm/src/fpm/manifest/package.f90
+++ b/fpm/src/fpm/manifest/package.f90
@@ -115,10 +115,10 @@ contains
call new_build_config(self%build, child, error)
if (allocated(error)) return
-
+
call get_value(table, "version", version, "0")
call new_version(self%version, version, error)
-
+
if (allocated(error)) return
call get_value(table, "dependencies", child, requested=.false.)
diff --git a/fpm/src/fpm_backend.f90 b/fpm/src/fpm_backend.f90
index 3cb95d7..632da64 100644
--- a/fpm/src/fpm_backend.f90
+++ b/fpm/src/fpm_backend.f90
@@ -8,7 +8,7 @@ use fpm_model, only: fpm_model_t, srcfile_t, build_target_t, FPM_UNIT_MODULE, &
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, &
FPM_UNIT_CSOURCE, FPM_UNIT_PROGRAM, &
FPM_SCOPE_TEST, FPM_TARGET_OBJECT, FPM_TARGET_ARCHIVE, FPM_TARGET_EXECUTABLE
-
+
use fpm_strings, only: split
implicit none
@@ -41,9 +41,9 @@ subroutine build_package(model)
linking = linking//" "//model%link_flags
do i=1,size(model%targets)
-
+
call build_target(model,model%targets(i)%ptr,linking)
-
+
end do
end subroutine build_package
@@ -52,7 +52,7 @@ end subroutine build_package
recursive subroutine build_target(model,target,linking)
! Compile Fortran source, called recursively on it dependents
- !
+ !
type(fpm_model_t), intent(in) :: model
type(build_target_t), intent(inout) :: target
character(:), allocatable, intent(in) :: linking
@@ -89,10 +89,10 @@ recursive subroutine build_target(model,target,linking)
target%dependencies(i)%ptr%target_type == FPM_TARGET_OBJECT) then
exe_obj => target%dependencies(i)%ptr
-
+
! Construct object list for executable
objs = " "//exe_obj%output_file
-
+
! Include non-library object dependencies
do j=1,size(exe_obj%dependencies)
@@ -107,7 +107,7 @@ recursive subroutine build_target(model,target,linking)
end if
end do
-
+
if (.not.exists(dirname(target%output_file))) then
call mkdir(dirname(target%output_file))
end if
@@ -115,7 +115,7 @@ recursive subroutine build_target(model,target,linking)
select case(target%target_type)
case (FPM_TARGET_OBJECT)
- call run("gfortran -c " // target%source%file_name // model%fortran_compile_flags &
+ call run(model%fortran_compiler//" -c " // target%source%file_name // model%fortran_compile_flags &
// " -o " // target%output_file)
case (FPM_TARGET_EXECUTABLE)
@@ -126,7 +126,7 @@ recursive subroutine build_target(model,target,linking)
end do
end if
- call run("gfortran " // objs // model%fortran_compile_flags &
+ call run(model%fortran_compiler // objs // model%fortran_compile_flags &
//link_flags// " -o " // target%output_file)
case (FPM_TARGET_ARCHIVE)
diff --git a/fpm/src/fpm_command_line.f90 b/fpm/src/fpm_command_line.f90
index 50a7d25..656fe5e 100644
--- a/fpm/src/fpm_command_line.f90
+++ b/fpm/src/fpm_command_line.f90
@@ -1,9 +1,9 @@
module fpm_command_line
-use fpm_environment, only : get_os_type, &
+use fpm_environment, only : get_os_type, get_env, &
OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_WINDOWS, &
OS_CYGWIN, OS_SOLARIS, OS_FREEBSD
use M_CLI2, only : set_args, lget, sget, unnamed, remaining, specified
-use fpm_strings, only : lower
+use fpm_strings, only : lower, split
use fpm_filesystem, only : basename, canon_path
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, &
& stdout=>output_unit, &
@@ -29,11 +29,14 @@ type, extends(fpm_cmd_settings) :: fpm_new_settings
logical :: with_test=.false.
logical :: with_lib=.true.
logical :: backfill=.true.
+ logical :: verbose=.true.
end type
type, extends(fpm_cmd_settings) :: fpm_build_settings
- logical :: release=.false.
logical :: list=.false.
+ character(len=:),allocatable :: compiler
+ character(len=:),allocatable :: build_name
+ logical :: verbose=.true.
end type
type, extends(fpm_build_settings) :: fpm_run_settings
@@ -43,14 +46,17 @@ type, extends(fpm_build_settings) :: fpm_run_settings
end type
type, extends(fpm_run_settings) :: fpm_test_settings
+integer :: gfortran_bug=0
end type
type, extends(fpm_cmd_settings) :: fpm_install_settings
+ logical :: verbose=.true.
end type
character(len=:),allocatable :: name
character(len=:),allocatable :: os_type
-character(len=ibug),allocatable :: names(:)
+character(len=ibug),allocatable :: names(:)
+character(len=:),allocatable :: tnames(:)
character(len=:), allocatable :: version_text(:)
character(len=:), allocatable :: help_new(:), help_fpm(:), help_run(:), &
@@ -61,7 +67,8 @@ character(len=20),parameter :: manual(*)=[ character(len=20) ::&
& ' ', 'fpm', 'new', 'build', 'run', &
& 'test', 'runner', 'list', 'help', 'version' ]
-character(len=:), allocatable :: charbug
+character(len=:), allocatable :: val_runner, val_build, val_compiler
+
contains
subroutine get_command_line_settings(cmd_settings)
class(fpm_cmd_settings), allocatable, intent(out) :: cmd_settings
@@ -102,7 +109,17 @@ contains
select case(trim(cmdarg))
case('run')
- call set_args('--list F --release F --runner " " --',help_run,version_text)
+ call set_args('&
+ & --target " " &
+ & --list F &
+ & --release F&
+ & --verbose F&
+ & --runner " " &
+ & --fc "'//basename(get_env('FPM_FC',get_env('FC','gfortran')))//'" &
+ & --compiler "'//basename(get_env('FPM_FC',get_env('FC','gfortran')))//'" &
+ & --',help_test,version_text)
+
+ call check_build_vals()
if( size(unnamed) .gt. 1 )then
names=unnamed(2:)
@@ -110,19 +127,48 @@ contains
names=[character(len=len(names)) :: ]
endif
+ if(specified('target') )then
+ call split(sget('target'),tnames,delimiters=' ,:')
+ names=[character(len=max(len(names),len(tnames))) :: names,tnames]
+ endif
+
allocate(fpm_run_settings :: cmd_settings)
- cmd_settings=fpm_run_settings( name=names, list=lget('list'), &
- & release=lget('release'), args=remaining ,runner=sget('runner') )
+ val_runner=sget('runner')
+ cmd_settings=fpm_run_settings(&
+ & args=remaining,&
+ & build_name=val_build,&
+ & compiler=val_compiler, &
+ & list=lget('list'),&
+ & name=names,&
+ & runner=val_runner,&
+ & verbose=lget('verbose') )
case('build')
- call set_args( '--release F --list F --',help_build,version_text )
+ call set_args( '&
+ & --release F &
+ & --list F &
+ & --verbose F&
+ & --fc "'//basename(get_env('FPM_FC',get_env('FC','gfortran')))//'" &
+ & --compiler "'//basename(get_env('FPM_FC',get_env('FC','gfortran')))//'" &
+ & --',help_test,version_text)
+
+ call check_build_vals()
allocate( fpm_build_settings :: cmd_settings )
- cmd_settings=fpm_build_settings( release=lget('release'), &
- & list=lget('list') )
+ cmd_settings=fpm_build_settings( &
+ & build_name=val_build,&
+ & compiler=val_compiler, &
+ & list=lget('list'),&
+ & verbose=lget('verbose') )
case('new')
- call set_args(' --src F --lib F --app F --test F --backfill F', &
+ call set_args('&
+ & --src F &
+ & --lib F &
+ & --app F &
+ & --test F &
+ & --backfill F&
+ & --verbose F',&
& help_new, version_text)
select case(size(unnamed))
case(1)
@@ -153,17 +199,21 @@ contains
allocate(fpm_new_settings :: cmd_settings)
if (any( specified(['src ','lib ','app ','test']) ) )then
- cmd_settings=fpm_new_settings(name=name, &
+ cmd_settings=fpm_new_settings(&
+ & backfill=lget('backfill'), &
+ & name=name, &
& with_executable=lget('app'), &
- & with_test=lget('test'), &
& with_lib=any([lget('lib'),lget('src')]), &
- & backfill=lget('backfill') )
+ & with_test=lget('test'), &
+ & verbose=lget('verbose') )
else
- cmd_settings=fpm_new_settings(name=name, &
+ cmd_settings=fpm_new_settings(&
+ & backfill=lget('backfill') , &
+ & name=name, &
& with_executable=.true., &
- & with_test=.true., &
& with_lib=.true., &
- & backfill=lget('backfill') )
+ & with_test=.true., &
+ & verbose=lget('verbose') )
endif
case('help','manual')
@@ -209,17 +259,32 @@ contains
call printhelp(help_text)
case('install')
- call set_args('--release F ', help_install, version_text)
+ call set_args('&
+ & --release F&
+ & --verbose F&
+ &', help_install, version_text)
allocate(fpm_install_settings :: cmd_settings)
case('list')
- call set_args(' --list F', help_list, version_text)
+ call set_args('&
+ & --list 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('--list F --release F --runner " " --',help_test,version_text)
+ call set_args('&
+ & --target " " &
+ & --list F&
+ & --release F&
+ & --runner " " &
+ & --fc "'//basename(get_env('FPM_FC',get_env('FC','gfortran')))//'" &
+ & --compiler "'//basename(get_env('FPM_FC',get_env('FC','gfortran')))//'" &
+ & --verbose F&
+ & --',help_test,version_text)
+
+ call check_build_vals()
if( size(unnamed) .gt. 1 )then
names=unnamed(2:)
@@ -227,10 +292,21 @@ contains
names=[character(len=len(names)) :: ]
endif
+ if(specified('target') )then
+ call split(sget('target'),tnames,delimiters=' ,:')
+ names=[character(len=max(len(names),len(tnames))) :: names,tnames]
+ endif
+
allocate(fpm_test_settings :: cmd_settings)
- charbug=sget('runner')
- cmd_settings=fpm_test_settings( name=names, list=lget('list'), &
- & release=lget('release'), args=remaining ,runner=charbug )
+ val_runner=sget('runner')
+ cmd_settings=fpm_test_settings(&
+ & args=remaining, &
+ & build_name=val_build, &
+ & compiler=val_compiler, &
+ & list=lget('list'), &
+ & name=names, &
+ & runner=val_runner, &
+ & verbose=lget('verbose') )
case default
@@ -253,10 +329,49 @@ contains
end select
contains
+
+ subroutine check_build_vals()
+ integer :: oneword
+ ! take basename of first word on FC; as other products
+ ! such as CMake allow FC to include optional compiler options
+ ! and others allow full pathnames to the decoder
+ val_compiler=''
+ val_compiler=sget('fc')
+ if(specified('compiler') )val_compiler=sget('compiler')
+ oneword=index(adjustl(val_compiler)//' ',' ')-1
+ val_compiler=val_compiler(:oneword)
+ if(val_compiler.eq.'') then
+ val_compiler='gfortran'
+ else
+ val_compiler=basename(val_compiler)
+ endif
+ if( specified('fc').and.specified('compiler') )then
+ write(stdout,'(a)')&
+ &'<WARNING> --fc and --compiler are aliases and should not both ', &
+ &' be specified. Using '//val_compiler
+ endif
+
+ if(.not.is_fortran_name(val_compiler))then
+ stop '<ERROR> compiler names must be simple names'
+ endif
+
+ val_build=trim(merge('release','debug ',lget('release')))
+
+ end subroutine check_build_vals
+
subroutine printhelp(lines)
character(len=:),intent(in),allocatable :: lines(:)
- write(stdout,'(g0)')(trim(lines(i)), i=1, size(lines) )
+ integer :: iii,ii
+ if(allocated(lines))then
+ ii=size(lines)
+ if(ii .gt. 0 .and. len(lines).gt. 0) then
+ write(stdout,'(g0)')(trim(lines(iii)), iii=1, ii)
+ else
+ write(stdout,'(a)')'<WARNING: *printhelp* output requested is empty'
+ endif
+ endif
end subroutine printhelp
+
end subroutine get_command_line_settings
function is_fortran_name(line) result (lout)
@@ -298,13 +413,13 @@ contains
' "fpm --help" or "fpm SUBCOMMAND --help" for detailed descriptions. ', &
' ']
help_list_dash = [character(len=80) :: &
- ' ', &
- ' build [--release] [--list] ', &
- ' help [NAME(s)] ', &
- ' new NAME [--lib|--src] [--app] [--test] [--backfill] ', &
- ' list [--list] ', &
- ' run [NAME(s)] [--release] [--runner "CMD"] [--list] [-- ARGS] ', &
- ' test [NAME(s)] [--release] [--runner "CMD"] [--list] [-- ARGS] ', &
+ ' ', &
+ ' build [-fc compiler] [--release] [--list] ', &
+ ' help [NAME(s)] ', &
+ ' new NAME [--lib|--src] [--app] [--test] [--backfill] ', &
+ ' list [--list] ', &
+ ' run [NAME(s)] [--release] [--runner "CMD"] [--list] [--fc compiler] [-- ARGS] ', &
+ ' test [NAME(s)] [--release] [--runner "CMD"] [--list][--fc compiler] [-- ARGS] ', &
' ']
help_usage=[character(len=80) :: &
'' ]
@@ -400,15 +515,17 @@ contains
'SUBCOMMANDS ', &
' Valid fpm(1) subcommands are: ', &
' ', &
- ' build [--release] [--list] ', &
+ ' build [--release] [--list] [-fc COMPILER] ', &
' Compile the packages into the "build/" directory. ', &
' new NAME [--lib|--src] [--app] [--test] [--backfill] ', &
' Create a new Fortran package directory ', &
' with sample files ', &
- ' run [NAME(s)] [--release] [--list] [--runner "CMD"][-- ARGS] ', &
+ ' run [NAME(s)] [--release] [--list] [--runner "CMD"] ', &
+ ' [--fc COMPILER] [-- ARGS] ', &
' Run the local package binaries. defaults to all ', &
' binaries for that release. ', &
- ' test [NAME(s)] [--release] [--list] [--runner "CMD"] [-- ARGS] ', &
+ ' test [NAME(s)] [--release] [--list] [--runner "CMD"] ', &
+ ' [--fc COMPILER] [-- ARGS] ', &
' Run the tests ', &
' help [NAME(s)] Alternate method for displaying subcommand help ', &
' list [--list] Display brief descriptions of all subcommands. ', &
@@ -421,7 +538,8 @@ contains
' optimization flags are used. ', &
' --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. ', &
+ ' --runner CMD Provides a command to prefix program execution paths. ', &
+ ' --fc COMPILER Compiler name. ', &
' -- ARGS Arguments to pass to executables. ', &
' --help Show help text and exit. Valid for all subcommands. ', &
' --version Show version information and exit. Valid for all ', &
@@ -470,7 +588,8 @@ contains
' run(1) - the fpm(1) subcommand to run project applications ', &
' ', &
'SYNOPSIS ', &
- ' fpm run [NAME(s)] [--release] [--runner "CMD"] [-- ARGS] ', &
+ ' fpm run [[--target] NAME(s)][--release][-fc compiler ] ', &
+ ' [--runner "CMD"] [--list][-- ARGS] ', &
' ', &
' fpm run --help|--version ', &
' ', &
@@ -478,14 +597,19 @@ contains
' Run applications you have built in your fpm(1) project. ', &
' ', &
'OPTIONS ', &
- ' NAME(s) optional list of specific names to execute. ', &
- ' The default is to run all the applications in app/ ', &
- ' or the programs listed in the "fpm.toml" file. ', &
+ ' --target NAME(s) optional list of specific names to execute. ', &
+ ' The default is to run all the applications in app/ ', &
+ ' or the programs listed in the "fpm.toml" file. ', &
' --release selects the optimized build instead of the debug ', &
' build. ', &
- ' --list list candidates instead of building or running them ', &
+ ' --fc COMPILER Specify a compiler name. The default can be set by the ', &
+ ' environment variable FPM_FC. If not set, the ', &
+ ' environment variable FC is used to set the default. ', &
+ ' If that is not set the name "gfortran" becomes the ', &
+ ' default. "--compiler" is an alias for "--fc". ', &
' --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 ', &
' -- ARGS optional arguments to pass to the program(s). ', &
' The same arguments are passed to all names ', &
' specified. ', &
@@ -495,12 +619,16 @@ contains
' ', &
' # run default programs in /app or as specified in "fpm.toml" ', &
' fpm run ', &
+
+ ' # run default programs in /app or as specified in "fpm.toml" ', &
+ ' # using the compiler command "f90". ', &
+ ' fpm run -fc f90 ', &
' ', &
' # run a specific program and pass arguments to the command ', &
' fpm run mytest -- -x 10 -y 20 --title "my title line" ', &
' ', &
' # run production version of two applications ', &
- ' fpm run prg1 prg2 --release ', &
+ ' fpm run --target prg1,prg2 --release ', &
' ', &
' # install executables in directory (assuming install(1) exists) ', &
' fpm run --runner ''install -b -m 0711 -p -t /usr/local/bin'' ', &
@@ -510,7 +638,7 @@ contains
' build(1) - the fpm(1) subcommand to build a project ', &
' ', &
'SYNOPSIS ', &
- ' fpm build [--release]|[-list] ', &
+ ' fpm build [--release][-fc COMPILER] [-list] ', &
' ', &
' fpm build --help|--version ', &
' ', &
@@ -533,6 +661,11 @@ contains
'OPTIONS ', &
' --release build in build/*_release instead of build/*_debug with ', &
' high optimization instead of full debug options. ', &
+ ' --fc COMPILER Specify a compiler name. The default can be set by the ', &
+ ' environment variable FPM_FC. If not set, the ', &
+ ' environment variable FC is used to set the default. ', &
+ ' If that is not set the name "gfortran" becomes the ', &
+ ' default. "--compiler" is an alias for "--fc". ', &
' --list list candidates instead of building or running them ', &
' --help print this help and exit ', &
' --version print program version information and exit ', &
@@ -654,7 +787,8 @@ contains
' test(1) - the fpm(1) subcommand to run project tests ', &
' ', &
'SYNOPSIS ', &
- ' fpm test [NAME(s)] [--release] [--list] [--runner "CMD"] [-- ARGS] ', &
+ ' fpm test [[--target] NAME(s)][--release][-fc compiler ] ', &
+ ' [--runner "CMD"] [--list][-- ARGS] ', &
' ', &
' fpm test --help|--version ', &
' ', &
@@ -662,14 +796,19 @@ contains
' Run applications you have built to test your project. ', &
' ', &
'OPTIONS ', &
- ' NAME(s) optional list of specific test names to execute. ', &
- ' The default is to run all the tests in test/ ', &
- ' or the tests listed in the "fpm.toml" file. ', &
+ ' --target NAME(s) optional list of specific test names to execute. ', &
+ ' The default is to run all the tests in test/ ', &
+ ' or the tests listed in the "fpm.toml" file. ', &
' --release selects the optimized build instead of the debug ', &
' build. ', &
- ' --list list candidates instead of building or running them ', &
+ ' --fc COMPILER Specify a compiler name. The default can be set by the ', &
+ ' environment variable FPM_FC. If not set, the ', &
+ ' environment variable FC is used to set the default. ', &
+ ' If that is not set the name "gfortran" becomes the ', &
+ ' default. "--compiler" is an alias for "--fc". ', &
' --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 ', &
' -- ARGS optional arguments to pass to the test program(s). ', &
' The same arguments are passed to all test names ', &
' specified. ', &
@@ -680,10 +819,13 @@ contains
' # run default tests in /test or as specified in "fpm.toml" ', &
' fpm test ', &
' ', &
+ ' # run using compiler command "f90" ', &
+ ' fpm test -fc f90 ', &
+ ' ', &
' # 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 # production version of two tests ', &
+ ' fpm test tst1 tst2 --release # run production version of two tests ', &
'' ]
help_install=[character(len=80) :: &
' fpm(1) subcommand "install" ', &
diff --git a/fpm/src/fpm_environment.f90 b/fpm/src/fpm_environment.f90
index 553aa8b..1a8afef 100644
--- a/fpm/src/fpm_environment.f90
+++ b/fpm/src/fpm_environment.f90
@@ -3,6 +3,7 @@ module fpm_environment
private
public :: get_os_type
public :: run
+ public :: get_env
integer, parameter, public :: OS_UNKNOWN = 0
integer, parameter, public :: OS_LINUX = 1
@@ -114,4 +115,37 @@ contains
error stop
end if
end subroutine run
+
+ function get_env(NAME,DEFAULT) result(VALUE)
+ implicit none
+ character(len=*),intent(in) :: NAME
+ character(len=*),intent(in),optional :: DEFAULT
+ character(len=:),allocatable :: VALUE
+ integer :: howbig
+ integer :: stat
+ integer :: length
+ ! get length required to hold value
+ length=0
+ if(NAME.ne.'')then
+ call get_environment_variable(NAME, length=howbig,status=stat,trim_name=.true.)
+ select case (stat)
+ case (1)
+ !*!print *, NAME, " is not defined in the environment. Strange..."
+ VALUE=''
+ case (2)
+ !*!print *, "This processor doesn't support environment variables. Boooh!"
+ VALUE=''
+ case default
+ ! make string to hold value of sufficient size
+ allocate(character(len=max(howbig,1)) :: VALUE)
+ ! get value
+ call get_environment_variable(NAME,VALUE,status=stat,trim_name=.true.)
+ if(stat.ne.0)VALUE=''
+ end select
+ else
+ VALUE=''
+ endif
+ if(VALUE.eq.''.and.present(DEFAULT))VALUE=DEFAULT
+ end function get_env
+
end module fpm_environment
diff --git a/fpm/src/fpm_filesystem.f90 b/fpm/src/fpm_filesystem.f90
index 4c12314..52c9b58 100644
--- a/fpm/src/fpm_filesystem.f90
+++ b/fpm/src/fpm_filesystem.f90
@@ -31,10 +31,18 @@ function basename(path,suffix) result (base)
if (with_suffix) then
call split(path,file_parts,delimiters='\/')
- base = trim(file_parts(size(file_parts)))
+ if(size(file_parts).gt.0)then
+ base = trim(file_parts(size(file_parts)))
+ else
+ base = ''
+ endif
else
call split(path,file_parts,delimiters='\/.')
- base = trim(file_parts(size(file_parts)-1))
+ if(size(file_parts).gt.0)then
+ base = trim(file_parts(size(file_parts)-1))
+ else
+ base = ''
+ endif
end if
end function basename
@@ -44,7 +52,7 @@ function canon_path(path) result(canon)
! Canonicalize path for comparison
! Handles path string redundancies
! Does not test existence of path
- !
+ !
! To be replaced by realpath/_fullname in stdlib_os
!
character(*), intent(in) :: path
@@ -98,7 +106,7 @@ function canon_path(path) result(canon)
end if
end if
-
+
temp(j:j) = nixpath(i:i)
j = j + 1
@@ -123,23 +131,23 @@ function dirname(path) result (dir)
end function dirname
-logical function is_dir(dir)
- character(*), intent(in) :: dir
- integer :: stat
+logical function is_dir(dir)
+ character(*), intent(in) :: dir
+ integer :: stat
- select case (get_os_type())
+ select case (get_os_type())
case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD)
- call execute_command_line("test -d " // dir , exitstat=stat)
+ call execute_command_line("test -d " // dir , exitstat=stat)
- case (OS_WINDOWS)
- call execute_command_line('cmd /c "if not exist ' // windows_path(dir) // '\ exit /B 1"', exitstat=stat)
+ case (OS_WINDOWS)
+ call execute_command_line('cmd /c "if not exist ' // windows_path(dir) // '\ exit /B 1"', exitstat=stat)
- end select
+ end select
- is_dir = (stat == 0)
+ is_dir = (stat == 0)
-end function is_dir
+end function is_dir
function join_path(a1,a2,a3,a4,a5) result(path)
@@ -286,7 +294,7 @@ recursive subroutine list_files(dir, files, recurse)
do i=1,size(files)
if (is_dir(files(i)%s)) then
- call list_files(files(i)%s, dir_files, recurse=.true.)
+ call list_files(files(i)%s, dir_files, recurse=.true.)
sub_dir_files = [sub_dir_files, dir_files]
end if
@@ -318,7 +326,7 @@ function get_temp_filename() result(tempfile)
type(c_ptr) :: c_tempfile_ptr
character(len=1), pointer :: c_tempfile(:)
-
+
interface
function c_tempnam(dir,pfx) result(tmp) bind(c,name="tempnam")
@@ -360,7 +368,7 @@ function windows_path(path) result(winpath)
winpath(idx:idx) = '\'
idx = index(winpath,'/')
end do
-
+
end function windows_path
@@ -379,7 +387,7 @@ function unix_path(path) result(nixpath)
nixpath(idx:idx) = '/'
idx = index(nixpath,'\')
end do
-
+
end function unix_path
end module fpm_filesystem
diff --git a/fpm/src/fpm_model.f90 b/fpm/src/fpm_model.f90
index 20f174b..3f14125 100644
--- a/fpm/src/fpm_model.f90
+++ b/fpm/src/fpm_model.f90
@@ -33,7 +33,7 @@ integer, parameter :: FPM_TARGET_ARCHIVE = 2
integer, parameter :: FPM_TARGET_OBJECT = 3
type srcfile_t
- ! Type for encapsulating a source file
+ ! Type for encapsulating a source file
! and it's metadata
character(:), allocatable :: file_name
! File path relative to cwd
diff --git a/fpm/src/fpm_sources.f90 b/fpm/src/fpm_sources.f90
index 5e42430..46d439c 100644
--- a/fpm/src/fpm_sources.f90
+++ b/fpm/src/fpm_sources.f90
@@ -5,7 +5,7 @@ use fpm_model, only: srcfile_t, fpm_model_t, &
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, &
FPM_UNIT_CSOURCE, FPM_UNIT_CHEADER, FPM_SCOPE_UNKNOWN, &
FPM_SCOPE_LIB, FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_TEST
-
+
use fpm_filesystem, only: basename, canon_path, dirname, join_path, read_lines, list_files
use fpm_strings, only: lower, split, str_ends_with, string_t, operator(.in.)
use fpm_manifest_executable, only: executable_config_t
@@ -119,9 +119,9 @@ end subroutine add_sources_from_dir
subroutine add_executable_sources(sources,executables,scope,auto_discover,error)
- ! Include sources from any directories specified
+ ! Include sources from any directories specified
! in [[executable]] entries and apply any customisations
- !
+ !
type(srcfile_t), allocatable, intent(inout), target :: sources(:)
class(executable_config_t), intent(in) :: executables(:)
integer, intent(in) :: scope
@@ -153,7 +153,7 @@ subroutine add_executable_sources(sources,executables,scope,auto_discover,error)
if (basename(sources(j)%file_name,suffix=.true.) == executables(i)%main .and.&
canon_path(dirname(sources(j)%file_name)) == &
canon_path(executables(i)%source_dir) ) then
-
+
sources(j)%exe_name = executables(i)%name
if (allocated(executables(i)%link)) then
exe_source%link_libraries = executables(i)%link
@@ -171,7 +171,7 @@ subroutine add_executable_sources(sources,executables,scope,auto_discover,error)
exe_source%link_libraries = executables(i)%link
end if
exe_source%unit_scope = scope
-
+
if (allocated(error)) return
if (.not.allocated(sources)) then
@@ -215,7 +215,7 @@ end subroutine get_executable_source_dirs
function parse_f_source(f_filename,error) result(f_source)
- ! Rudimentary scan of Fortran source file and
+ ! Rudimentary scan of Fortran source file and
! extract program unit name and use/include dependencies
!
character(*), intent(in) :: f_filename
@@ -313,7 +313,7 @@ function parse_f_source(f_filename,error) result(f_source)
if (index(adjustl(file_lines(i)%s(ic+7:)),'"') == 1 .or. &
index(adjustl(file_lines(i)%s(ic+7:)),"'") == 1 ) then
-
+
n_include = n_include + 1
if (pass == 2) then
@@ -400,7 +400,7 @@ function parse_f_source(f_filename,error) result(f_source)
if (index(temp_string,':') > 0) then
temp_string = temp_string(index(temp_string,':')+1:)
-
+
end if
if (.not.validate_name(temp_string)) then
@@ -467,7 +467,7 @@ function parse_f_source(f_filename,error) result(f_source)
(name(i:i) >= '0' .and. name(i:i) <= '9').or. &
(lower(name(i:i)) >= 'a' .and. lower(name(i:i)) <= 'z').or. &
name(i:i) == '_') ) then
-
+
valid = .false.
return
end if
@@ -483,7 +483,7 @@ end function parse_f_source
function parse_c_source(c_filename,error) result(c_source)
- ! Rudimentary scan of c source file and
+ ! Rudimentary scan of c source file and
! extract include dependencies
!
character(*), intent(in) :: c_filename
@@ -519,7 +519,7 @@ function parse_c_source(c_filename,error) result(c_source)
! Process 'INCLUDE' statements
if (index(adjustl(lower(file_lines(i)%s)),'#include') == 1 .and. &
index(file_lines(i)%s,'"') > 0) then
-
+
n_include = n_include + 1
if (pass == 2) then
@@ -555,7 +555,7 @@ function split_n(string,delims,n,stat) result(substring)
! n=0 will return the last item
! n=-1 will return the penultimate item etc.
!
- ! stat = 1 on return if the index
+ ! stat = 1 on return if the index
! is not found
!
character(*), intent(in) :: string
diff --git a/fpm/src/fpm_strings.f90 b/fpm/src/fpm_strings.f90
index a6511c9..b94e80b 100644
--- a/fpm/src/fpm_strings.f90
+++ b/fpm/src/fpm_strings.f90
@@ -44,7 +44,7 @@ function f_string(c_string)
do i=1,n
f_string(i:i) = c_string(i)
end do
-
+
end function f_string
@@ -100,7 +100,7 @@ subroutine split(input_line,array,delimiters,order,nulls)
! Author: John S. Urban
! License: Public Domain
-
+
! given a line of structure " par1 par2 par3 ... parn " store each par(n) into a separate variable in array.
! o by default adjacent delimiters in the input string do not create an empty string in the output array
! o no quoting of delimiters is supported
@@ -109,7 +109,7 @@ subroutine split(input_line,array,delimiters,order,nulls)
character(len=*),optional,intent(in) :: order ! order of output array sequential|[reverse|right]
character(len=*),optional,intent(in) :: nulls ! return strings composed of delimiters or not ignore|return|ignoreend
character(len=:),allocatable,intent(out) :: array(:) ! output array of tokens
-
+
integer :: n ! max number of strings INPUT_LINE could split into if all delimiter
integer,allocatable :: ibegin(:) ! positions in input string where tokens start
integer,allocatable :: iterm(:) ! positions in input string where tokens end
@@ -126,7 +126,7 @@ subroutine split(input_line,array,delimiters,order,nulls)
integer :: inotnull ! count strings not composed of delimiters
integer :: ireturn ! number of tokens returned
integer :: imax ! length of longest token
-
+
! decide on value for optional DELIMITERS parameter
if (present(delimiters)) then ! optional delimiter list was present
if(delimiters.ne.'')then ! if DELIMITERS was specified and not null use it
diff --git a/fpm/src/fpm_targets.f90 b/fpm/src/fpm_targets.f90
index c3a59fd..9a29431 100644
--- a/fpm/src/fpm_targets.f90
+++ b/fpm/src/fpm_targets.f90
@@ -23,14 +23,14 @@ subroutine targets_from_sources(model,sources)
model%package_name,'lib'//model%package_name//'.a'))
do i=1,size(sources)
-
+
select case (sources(i)%unit_type)
case (FPM_UNIT_MODULE,FPM_UNIT_SUBMODULE,FPM_UNIT_SUBPROGRAM,FPM_UNIT_CSOURCE)
call add_target(model%targets,source = sources(i), &
type = FPM_TARGET_OBJECT,&
output_file = get_object_name(sources(i)))
-
+
if (with_lib .and. sources(i)%unit_scope == FPM_SCOPE_LIB) then
! Archive depends on object
call add_dependency(model%targets(1)%ptr, model%targets(size(model%targets))%ptr)
@@ -42,7 +42,7 @@ subroutine targets_from_sources(model,sources)
output_file = get_object_name(sources(i)), &
source = sources(i) &
)
-
+
if (sources(i)%unit_scope == FPM_SCOPE_APP) then
call add_target(model%targets,type = FPM_TARGET_EXECUTABLE,&
link_libraries = sources(i)%link_libraries, &
@@ -51,7 +51,7 @@ subroutine targets_from_sources(model,sources)
call add_target(model%targets,type = FPM_TARGET_EXECUTABLE,&
link_libraries = sources(i)%link_libraries, &
output_file = join_path(model%output_directory,'test',sources(i)%exe_name))
-
+
end if
! Executable depends on object
@@ -61,7 +61,7 @@ subroutine targets_from_sources(model,sources)
! Executable depends on library
call add_dependency(model%targets(size(model%targets))%ptr, model%targets(1)%ptr)
end if
-
+
end select
end do
@@ -70,20 +70,20 @@ subroutine targets_from_sources(model,sources)
function get_object_name(source) result(object_file)
! Generate object target path from source name and model params
- !
+ !
!
type(srcfile_t), intent(in) :: source
character(:), allocatable :: object_file
-
+
integer :: i
character(1), parameter :: filesep = '/'
character(:), allocatable :: dir
-
+
object_file = canon_path(source%file_name)
! Ignore first directory level
object_file = object_file(index(object_file,filesep)+1:)
-
+
! Convert any remaining directory separators to underscores
i = index(object_file,filesep)
do while(i > 0)
@@ -101,9 +101,9 @@ subroutine targets_from_sources(model,sources)
case default
object_file = join_path(model%output_directory,model%package_name,object_file)//'.o'
-
+
end select
-
+
end function get_object_name
end subroutine targets_from_sources
@@ -143,7 +143,7 @@ subroutine add_target(targets,type,output_file,source,link_libraries)
if (present(source)) new_target%source = source
if (present(link_libraries)) new_target%link_libraries = link_libraries
allocate(new_target%dependencies(0))
-
+
targets = [targets, build_target_ptr(new_target)]
end subroutine add_target
@@ -171,7 +171,7 @@ subroutine resolve_module_dependencies(targets,error)
integer :: i, j
do i=1,size(targets)
-
+
if (.not.allocated(targets(i)%ptr%source)) cycle
do j=1,size(targets(i)%ptr%source%modules_used)
@@ -180,7 +180,7 @@ subroutine resolve_module_dependencies(targets,error)
! Dependency satisfied in same file, skip
cycle
end if
-
+
if (targets(i)%ptr%source%unit_scope == FPM_SCOPE_APP .OR. &
targets(i)%ptr%source%unit_scope == FPM_SCOPE_TEST ) then
dep%ptr => &
@@ -203,7 +203,7 @@ subroutine resolve_module_dependencies(targets,error)
end do
- end do
+ end do
end subroutine resolve_module_dependencies
@@ -244,7 +244,7 @@ function find_module_dependency(targets,module_name,include_dir) result(target_p
end if
end do
-
+
end do
end function find_module_dependency
diff --git a/fpm/test/cli_test/cli_test.f90 b/fpm/test/cli_test/cli_test.f90
index 915d9da..fdb7979 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
-logical :: release,act_release ; namelist/act_cli/act_release
+character(len=63) :: build_name,act_build_name ; namelist/act_cli/act_build_name
character(len=:),allocatable :: args,act_args ; namelist/act_cli/act_args
-namelist/expected/cmd,cstat,estat,w_e,w_t,name,release,args
+namelist/expected/cmd,cstat,estat,w_e,w_t,name,build_name,args
integer :: lun
logical,allocatable :: tally(:)
logical,allocatable :: subtally(:)
@@ -50,19 +50,19 @@ 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",RELEASE=T,', &
+'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",RELEASE=T ARGS="""arg1"" -x ""and a long one""", ', &
+ &NAME="proj1","p2","project3",build_name="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",RELEASE=T,', &
+'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",RELEASE=T ARGS="""arg1"" -x ""and a long one""", ', &
+ &NAME="proj1","p2","project3",build_name="release" ARGS="""arg1"" -x ""and a long one""", ', &
-'CMD="build", NAME= RELEASE=F,ARGS="",', &
-'CMD="build --release", NAME= RELEASE=T,ARGS="",', &
+'CMD="build", NAME= build_name="debug",ARGS="",', &
+'CMD="build --release", NAME= build_name="release",ARGS="",', &
' ' ]
character(len=256) :: readme(3)
@@ -90,7 +90,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
- release=.false. ! --release
+ build_name="debug" ! --release
w_e=.false. ! --app
w_t=.false. ! --test
args=repeat(' ',132) ! -- ARGS
@@ -107,7 +107,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_release=.false.
+ act_build_name='debug'
act_w_e=.false.
act_w_t=.false.
act_args=repeat(' ',132)
@@ -119,7 +119,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_release.eqv.release)
+ call test_test('RELEASE',act_build_name.eq.build_name)
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)
@@ -203,7 +203,7 @@ allocate (character(len=len(name)) :: act_name(0) )
act_args=''
act_w_e=.false.
act_w_t=.false.
-act_release=.false.
+act_build_name='debug'
select type(settings=>cmd_settings)
type is (fpm_new_settings)
@@ -211,13 +211,13 @@ type is (fpm_new_settings)
act_w_t=settings%with_test
act_name=[trim(settings%name)]
type is (fpm_build_settings)
- act_release=settings%release
+ act_build_name=settings%build_name
type is (fpm_run_settings)
- act_release=settings%release
+ act_build_name=settings%build_name
act_name=settings%name
act_args=settings%args
type is (fpm_test_settings)
- act_release=settings%release
+ act_build_name=settings%build_name
act_name=settings%name
act_args=settings%args
type is (fpm_install_settings)