aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJohn S. Urban <urbanjost@comcast.net>2021-03-02 21:02:25 -0500
committerJohn S. Urban <urbanjost@comcast.net>2021-03-02 21:02:25 -0500
commitb406adfb30b445bceb693d3369d3875255bc671e (patch)
treebad9d9ac003cfc155c0370d304a9af7c2ab54e85
parent59837ec4eb1ca6533fd82c84a0d5d7fe7e7a233d (diff)
downloadfpm-b406adfb30b445bceb693d3369d3875255bc671e.tar.gz
fpm-b406adfb30b445bceb693d3369d3875255bc671e.zip
--all is back; --list is compact
-rw-r--r--fpm/src/fpm.f9076
-rw-r--r--fpm/src/fpm_command_line.f9053
-rw-r--r--fpm/src/fpm_environment.f9013
3 files changed, 86 insertions, 56 deletions
diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90
index 24ad471..e2ed356 100644
--- a/fpm/src/fpm.f90
+++ b/fpm/src/fpm.f90
@@ -210,8 +210,7 @@ subroutine cmd_run(settings,test)
class(fpm_run_settings), intent(in) :: settings
logical, intent(in) :: test
- integer, parameter :: LINE_WIDTH = 80
- integer :: i, j, col_width, nCol
+ integer :: i, j, col_width
logical :: found(size(settings%name))
type(error_t), allocatable :: error
type(package_config_t) :: package
@@ -222,6 +221,7 @@ subroutine cmd_run(settings,test)
type(srcfile_t), pointer :: exe_source
integer :: run_scope
character(len=:),allocatable :: line
+ logical :: toomany
call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
if (allocated(error)) then
@@ -297,8 +297,11 @@ subroutine cmd_run(settings,test)
! Check all names are valid
! or no name and found more than one file
- if ( any(.not.found) .or. &
- & (size(settings%name).eq.0 .and. size(executables).gt.1 .and. .not.test) .and.&
+ toomany= size(settings%name).eq.0 .and. size(executables).gt.1
+ if ( any(.not.found) &
+ & .or. &
+ & ( (toomany .and. .not.test) .or. (toomany .and. settings%runner .ne. '') ) &
+ & .and. &
& .not.settings%list) then
line=join(settings%name)
if(line.ne.'.')then ! do not report these special strings
@@ -315,6 +318,39 @@ subroutine cmd_run(settings,test)
endif
endif
+ call compact_list()
+
+ if(line.eq.'.' .or. line.eq.' ')then ! do not report these special strings
+ stop
+ else
+ stop 1
+ endif
+
+ end if
+
+ call build_package(model)
+
+ if (settings%list) then
+ call compact_list()
+ else
+
+ do i=1,size(executables)
+ if (exists(executables(i)%s)) then
+ if(settings%runner .ne. ' ')then
+ call run(settings%runner//' '//executables(i)%s//" "//settings%args,echo=settings%verbose)
+ else
+ call run(executables(i)%s//" "//settings%args,echo=settings%verbose)
+ endif
+ else
+ write(stderr,*)'fpm::run<ERROR>',executables(i)%s,' not found'
+ stop 1
+ end if
+ end do
+ endif
+ contains
+ subroutine compact_list()
+ integer, parameter :: LINE_WIDTH = 80
+ integer :: i, j, nCol
j = 1
nCol = LINE_WIDTH/col_width
write(stderr,*) 'Available names:'
@@ -334,40 +370,10 @@ subroutine cmd_run(settings,test)
j = j + 1
end if
-
end if
-
end do
-
write(stderr,*)
- if(line.eq.'.' .or. line.eq.' ')then ! do not report these special strings
- stop
- else
- stop 1
- endif
-
- end if
-
- call build_package(model)
-
- do i=1,size(executables)
- if (settings%list) then
- write(stderr,*) executables(i)%s
- else
-
- if (exists(executables(i)%s)) then
- if(settings%runner .ne. ' ')then
- call run(settings%runner//' '//executables(i)%s//" "//settings%args)
- else
- call run(executables(i)%s//" "//settings%args)
- endif
- else
- write(stderr,*)'fpm::run<ERROR>',executables(i)%s,' not found'
- stop 1
- end if
-
- end if
- end do
+ end subroutine compact_list
end subroutine cmd_run
diff --git a/fpm/src/fpm_command_line.f90 b/fpm/src/fpm_command_line.f90
index 6a790ec..72f89b8 100644
--- a/fpm/src/fpm_command_line.f90
+++ b/fpm/src/fpm_command_line.f90
@@ -152,6 +152,7 @@ contains
call set_args('&
& --target " " &
& --list F &
+ & --all F &
& --release F&
& --example F&
& --runner " " &
@@ -167,11 +168,17 @@ 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
+ ! convert --all to '*'
+ if(lget('all'))then
+ names=[character(len=max(len(names),1)) :: names,'*' ]
+ endif
+
! convert special string '..' to equivalent (shorter) '*'
! to allow for a string that does not require shift-key and quoting
do i=1,size(names)
@@ -180,6 +187,7 @@ contains
allocate(fpm_run_settings :: cmd_settings)
val_runner=sget('runner')
+ if(specified('runner') .and. val_runner.eq.'')val_runner='echo'
cmd_settings=fpm_run_settings(&
& args=remaining,&
& build_name=val_build,&
@@ -389,6 +397,7 @@ contains
allocate(fpm_test_settings :: cmd_settings)
val_runner=sget('runner')
+ if(specified('runner') .and. val_runner.eq.'')val_runner='echo'
cmd_settings=fpm_test_settings(&
& args=remaining, &
& build_name=val_build, &
@@ -513,7 +522,7 @@ contains
' [--full|--bare][--backfill] ', &
' update [NAME(s)] [--fetch-only] [--clean] [--verbose] ', &
' list [--list] ', &
- ' run [[--target] NAME(s) [--example] [--release] [--runner "CMD"] ', &
+ ' run [[--target] NAME(s) [--example] [--release] [-all] [--runner "CMD"] ', &
' [--compiler COMPILER_NAME] [--list] [-- ARGS] ', &
' test [[--target] NAME(s)] [--release] [--runner "CMD"] [--list] ', &
' [--compiler COMPILER_NAME] [-- ARGS] ', &
@@ -541,7 +550,8 @@ contains
'OPTION ', &
' --runner ''CMD'' quoted command used to launch the fpm(1) executables. ', &
' Available for both the "run" and "test" subcommands. ', &
- ' ', &
+ ' If the keyword is specified without a value the default command ', &
+ ' is "echo". ', &
' -- SUFFIX_OPTIONS additional options to suffix the command CMD and executable ', &
' file names with. ', &
'EXAMPLES ', &
@@ -626,7 +636,7 @@ contains
' new NAME [[--lib|--src] [--app] [--test] [--example]]| ', &
' [--full|--bare][--backfill] ', &
' update [NAME(s)] [--fetch-only] [--clean] ', &
- ' run [[--target] NAME(s)] [--release] [--list] [--example] ', &
+ ' run [[--target] NAME(s)] [--release] [--list] [--example] [-all] ', &
' [--runner "CMD"] [--compiler COMPILER_NAME] [-- ARGS] ', &
' test [[--target] NAME(s)] [--release] [--list] ', &
' [--runner "CMD"] [--compiler COMPILER_NAME] [-- ARGS] ', &
@@ -699,7 +709,7 @@ contains
' ', &
'SYNOPSIS ', &
' fpm run [[--target] NAME(s)[--release][--compiler COMPILER_NAME] ', &
- ' [--runner "CMD"] [--example] [--list][-- ARGS] ', &
+ ' [--runner "CMD"] [--example] [--list] [--all] [-- ARGS] ', &
' ', &
' fpm run --help|--version ', &
' ', &
@@ -711,17 +721,17 @@ contains
' are automatically rebuilt before being run if they are out of date. ', &
' ', &
'OPTIONS ', &
- ' --target NAME(s) list of specific application names to execute. ', &
- ' No name is required if only one target exists. ', &
- ' If no name is supplied and more than one candidate ', &
- ' exists or a name has no match a list is produced ', &
- ' and fpm(1) exits. ', &
- ' Basic "globbing" is supported where "?" represents', &
+ ' --target NAME(s) list of application names to execute. No name is ', &
+ ' required if only one target exists. If no name is ', &
+ ' supplied and more than one candidate exists or a ', &
+ ' name has no match a list is produced and fpm(1) ', &
+ ' exits. ', &
+ ' ', &
+ ' Basic "globbing" is supported where "?" represents ', &
' any single character and "*" represents any string. ', &
- ' The special string "." causes all targets to ', &
- ' be listed, even if only a single target exists. ', &
- ' The special string ".." causes all targets to ', &
- ' be executed. ', &
+ ' Note The glob string normally needs quoted to ', &
+ ' 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. ', &
' --compiler COMPILER_NAME Specify a compiler name. The default is ', &
@@ -738,9 +748,9 @@ contains
'EXAMPLES ', &
' fpm(1) - run or display project applications: ', &
' ', &
- ' fpm run # run a target when only one exists or list targets ', &
- ' fpm run . # list all targets, running nothing ', &
- ' fpm run .. # run all targets, no matter how many there are ', &
+ ' fpm run # run a target when only one exists or list targets ', &
+ ' fpm run --list # list all targets, running nothing. ', &
+ ' fpm run --all # run all targets, no matter how many there are. ', &
' ', &
' # run default program built or to be built with the compiler command ', &
' # "f90". If more than one app exists a list displays and target names', &
@@ -930,9 +940,9 @@ contains
' cd myproject # Enter the new directory ', &
' # and run commands such as ', &
' fpm build ', &
- ' fpm run # run example application program(s) ', &
+ ' fpm run # run lone example application program ', &
' fpm test # run example test program(s) ', &
- ' fpm run --example # run example program(s) ', &
+ ' fpm run --example # run lone example program ', &
' ', &
' fpm new A --full # create example/ and an annotated fpm.toml as well', &
' fpm new A --bare # create no directories ', &
@@ -956,6 +966,11 @@ contains
' --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. ', &
+ ' ', &
+ ' Basic "globbing" is supported where "?" represents ', &
+ ' 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. ', &
' --compiler COMPILER_NAME Specify a compiler name. The default is ', &
diff --git a/fpm/src/fpm_environment.f90 b/fpm/src/fpm_environment.f90
index 181252d..929a704 100644
--- a/fpm/src/fpm_environment.f90
+++ b/fpm/src/fpm_environment.f90
@@ -117,10 +117,19 @@ contains
unix = os /= OS_WINDOWS
end function os_is_unix
- subroutine run(cmd)
+ subroutine run(cmd,echo)
character(len=*), intent(in) :: cmd
+ logical,intent(in),optional :: echo
+ logical :: echo_local
integer :: stat
- print *, '+ ', cmd
+
+ if(present(echo))then
+ echo_local=echo
+ else
+ echo_local=.true.
+ endif
+ if(echo_local) print *, '+ ', cmd
+
call execute_command_line(cmd, exitstat=stat)
if (stat /= 0) then
print *, 'Command failed'