diff options
author | John S. Urban <urbanjost@comcast.net> | 2021-03-01 20:53:25 -0500 |
---|---|---|
committer | John S. Urban <urbanjost@comcast.net> | 2021-03-01 20:53:25 -0500 |
commit | ab57ec6b225edf848229e8f9f1cabecb6e508ade (patch) | |
tree | a18f01e4a93d5aa99a6faa3b832e6d0350765ab3 | |
parent | 90e1409f4e61899c8f1fb052888c794f3bcdb11e (diff) | |
download | fpm-ab57ec6b225edf848229e8f9f1cabecb6e508ade.tar.gz fpm-ab57ec6b225edf848229e8f9f1cabecb6e508ade.zip |
remove --add and add .
The default behavior becomes very similar to the Rust cargo(1)
package manager in that
# run application if there is one target
fpm run -- ARGS cargo run -- ARGS
fpm run NAME(S) cargo run --example NAME
fpm run --example NAME(S) cargo run --example NAME
fpm run --compiler CMP cargo --profile PROFILE-NAME
DIFFERENCES:
<-- fpm allows multiple names
<-- fpm does not have profiles, just compiler at this time
<-- fpm allows for quoted globbing strings which lets you
easily select all or groups by name substrings
<-- fpm lists available targets if an unknown name or no
name and multiple targets are available, or if special
name "." is specified. From the documentation I do not
see anything indicating if cargo(1) lists targets or
not.
So the common cases are very similiar, with extensions in fpm
to list and run groups of applications using a few special
globbing strings (just going from the cargo documentation; it
might behave differently).
-rw-r--r-- | fpm/src/fpm.f90 | 32 | ||||
-rw-r--r-- | fpm/src/fpm_command_line.f90 | 36 | ||||
-rw-r--r-- | fpm/src/fpm_strings.f90 | 197 |
3 files changed, 144 insertions, 121 deletions
diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90 index ec5e641..4ee9642 100644 --- a/fpm/src/fpm.f90 +++ b/fpm/src/fpm.f90 @@ -1,5 +1,5 @@ module fpm -use fpm_strings, only: string_t, operator(.in.), glob +use fpm_strings, only: string_t, operator(.in.), glob, join use fpm_backend, only: build_package use fpm_command_line, only: fpm_build_settings, fpm_new_settings, & fpm_run_settings, fpm_install_settings, fpm_test_settings @@ -221,6 +221,7 @@ subroutine cmd_run(settings,test) type(build_target_t), pointer :: exe_target type(srcfile_t), pointer :: exe_source integer :: run_scope + character(len=:),allocatable :: line call get_package_data(package, "fpm.toml", error, apply_defaults=.true.) if (allocated(error)) then @@ -299,16 +300,19 @@ subroutine cmd_run(settings,test) if ( any(.not.found) .or. & & (size(settings%name).eq.0 .and. size(executables).gt.1 .and. .not.test) .and.& & .not.settings%list) then - if(any(.not.found))then - write(stderr,'(A)',advance="no")'fpm::run<ERROR> specified names ' - do j=1,size(settings%name) - if (.not.found(j)) write(stderr,'(A)',advance="no") '"'//trim(settings%name(j))//'" ' - end do - write(stderr,'(A)') 'not found.' - write(stderr,*) - else if(settings%verbose)then - write(stderr,'(A)',advance="yes")'<INFO>when more than one executable is available' - write(stderr,'(A)',advance="yes")' program names must be specified.' + line=join(settings%name) + if(line.ne.'.'.and. line.ne.'..')then ! do not report these special strings + if(any(.not.found))then + write(stderr,'(A)',advance="no")'fpm::run<ERROR> specified names ' + do j=1,size(settings%name) + if (.not.found(j)) write(stderr,'(A)',advance="no") '"'//trim(settings%name(j))//'" ' + end do + write(stderr,'(A)') 'not found.' + write(stderr,*) + else if(settings%verbose)then + write(stderr,'(A)',advance="yes")'<INFO>when more than one executable is available' + write(stderr,'(A)',advance="yes")' program names must be specified.' + endif endif j = 1 @@ -336,7 +340,11 @@ subroutine cmd_run(settings,test) end do write(stderr,*) - stop 1 + if(line.eq.'.' .or. line.eq.' '.or. line.eq.'..')then ! do not report these special strings + stop + else + stop 1 + endif end if diff --git a/fpm/src/fpm_command_line.f90 b/fpm/src/fpm_command_line.f90 index f6712fd..31bb05f 100644 --- a/fpm/src/fpm_command_line.f90 +++ b/fpm/src/fpm_command_line.f90 @@ -152,7 +152,6 @@ contains call set_args('& & --target " " & & --list F & - & --all F & & --release F& & --example F& & --runner " " & @@ -172,9 +171,6 @@ contains call split(sget('target'),tnames,delimiters=' ,:') names=[character(len=max(len(names),len(tnames))) :: names,tnames] endif - if(lget('all'))then - names=[character(len=max(len(names),1)) :: names,'*'] - endif allocate(fpm_run_settings :: cmd_settings) val_runner=sget('runner') @@ -505,7 +501,7 @@ contains ' [--full|--bare][--backfill] ', & ' update [NAME(s)] [--fetch-only] [--clean] [--verbose] ', & ' list [--list] ', & - ' run [[--target] NAME(s)|--all] [--example] [--release] [--runner "CMD"] ', & + ' run [[--target] NAME(s) [--example] [--release] [--runner "CMD"] ', & ' [--compiler COMPILER_NAME] [--list] [-- ARGS] ', & ' test [[--target] NAME(s)] [--release] [--runner "CMD"] [--list] ', & ' [--compiler COMPILER_NAME] [-- ARGS] ', & @@ -618,7 +614,7 @@ contains ' new NAME [[--lib|--src] [--app] [--test] [--example]]| ', & ' [--full|--bare][--backfill] ', & ' update [NAME(s)] [--fetch-only] [--clean] ', & - ' run [[--target] NAME(s)|--all] [--release] [--list] [--example] ', & + ' run [[--target] NAME(s)] [--release] [--list] [--example] ', & ' [--runner "CMD"] [--compiler COMPILER_NAME] [-- ARGS] ', & ' test [[--target] NAME(s)] [--release] [--list] ', & ' [--runner "CMD"] [--compiler COMPILER_NAME] [-- ARGS] ', & @@ -690,7 +686,7 @@ contains ' run(1) - the fpm(1) subcommand to run project applications ', & ' ', & 'SYNOPSIS ', & - ' fpm run [[--target] NAME(s)|-all][--release][--compiler COMPILER_NAME]', & + ' fpm run [[--target] NAME(s)[--release][--compiler COMPILER_NAME] ', & ' [--runner "CMD"] [--example] [--list][-- ARGS] ', & ' ', & ' fpm run --help|--version ', & @@ -703,15 +699,16 @@ 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 application 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. ', & - ' Simple "globbing" is supported where "?" represents ', & - ' any single character and "*" represents any string. ', & - ' Therefore a quoted asterisk ''*'' runs all programs. ', & - ' --all An alias for "--target ''*''". All targets are selected. ', & + ' --target NAME(s) list of specific application names to execute. ', & + ' No name is required if only one application 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. ', & + ' Simple "globbing" is supported where "?" represents', & + ' any single character and "*" represents any string. ', & + ' Therefore a quoted asterisk ''*'' runs all programs. ', & + ' The special string "." also causes all targets to ', & + ' be listed, even if only a single target exists. ', & ' --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 ', & @@ -726,10 +723,11 @@ contains ' arguments are passed to all program names specified. ', & ' ', & 'EXAMPLES ', & - ' fpm(1) - run project applications: ', & + ' fpm(1) - run or display project applications: ', & ' ', & - ' # run all default programs in /app or as specified in "fpm.toml" ', & - ' fpm run --all ', & + ' fpm run # run a target when only one exists or list targets ', & + ' fpm run ''*'' # run all targets ', & + ' fpm run . # list all targets, running nothing ', & ' ', & ' # 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', & diff --git a/fpm/src/fpm_strings.f90 b/fpm/src/fpm_strings.f90 index 5b88591..7623e43 100644 --- a/fpm/src/fpm_strings.f90 +++ b/fpm/src/fpm_strings.f90 @@ -383,93 +383,103 @@ subroutine resize_string(list, n) end subroutine resize_string -pure function join(str,sep,trm,left,right) result (string) - -!> M_strings::join(3f): append an array of character variables with specified separator into a single CHARACTER variable -!> -!>##NAME -!> join(3f) - [M_strings:EDITING] append CHARACTER variable array into -!> a single CHARACTER variable with specified separator -!> (LICENSE:PD) -!> -!>##SYNOPSIS -!> -!> pure function join(str,sep,trm,left,right) result (string) -!> -!> character(len=*),intent(in) :: str(:) -!> character(len=*),intent(in),optional :: sep -!> logical,intent(in),optional :: trm -!> character(len=*),intent(in),optional :: right -!> character(len=*),intent(in),optional :: left -!> character(len=:),allocatable :: string -!> -!>##DESCRIPTION -!> JOIN(3f) appends the elements of a CHARACTER array into a single -!> CHARACTER variable, with elements 1 to N joined from left to right. -!> By default each element is trimmed of trailing spaces and the -!> default separator is a null string. -!> -!>##OPTIONS -!> STR(:) array of CHARACTER variables to be joined -!> SEP separator string to place between each variable. defaults -!> to a null string. -!> LEFT string to place at left of each element -!> RIGHT string to place at right of each element -!> TRM option to trim each element of STR of trailing -!> spaces. Defaults to .TRUE. -!> -!>##RESULT -!> STRING CHARACTER variable composed of all of the elements of STR() -!> appended together with the optional separator SEP placed -!> between the elements and optional left and right elements. -!> -!>##EXAMPLE +pure function join(str,sep,trm,left,right,start,end) result (string) !> -!> Sample program: -!> -!> program demo_join -!> use M_strings, only: join -!> implicit none -!> character(len=:),allocatable :: s(:) -!> character(len=:),allocatable :: out -!> integer :: i -!> s=[character(len=10) :: 'United',' we',' stand,', & -!> & ' divided',' we fall.'] -!> out=join(s) -!> write(*,'(a)') out -!> write(*,'(a)') join(s,trm=.false.) -!> write(*,'(a)') (join(s,trm=.false.,sep='|'),i=1,3) -!> write(*,'(a)') join(s,sep='<>') -!> write(*,'(a)') join(s,sep=';',left='[',right=']') -!> write(*,'(a)') join(s,left='[',right=']') -!> write(*,'(a)') join(s,left='>>') -!> end program demo_join -!> -!> Expected output: -!> -!> United we stand, divided we fall. -!> United we stand, divided we fall. -!> United | we | stand, | divided | we fall. | -!> United | we | stand, | divided | we fall. | -!> United | we | stand, | divided | we fall. | -!> United<> we<> stand,<> divided<> we fall.<> -!> [United];[ we];[ stand,];[ divided];[ we fall.]; -!> [United][ we][ stand,][ divided][ we fall.] -!> >>United>> we>> stand,>> divided>> we fall. -!> -!>##AUTHOR -!> John S. Urban -!> -!>##LICENSE -!> Public Domain - -character(len=*),intent(in) :: str(:) -character(len=*),intent(in),optional :: sep, right, left -logical,intent(in),optional :: trm -character(len=:),allocatable :: string -integer :: i -logical :: trm_local -character(len=:),allocatable :: sep_local, left_local, right_local +!!##NAME +!! join(3f) - [fpm_strings:EDITING] append CHARACTER variable array into +!! a single CHARACTER variable with specified separator +!! (LICENSE:PD) +!! +!!##SYNOPSIS +!! +!! pure function join(str,sep,trm,left,right,start,end) result (string) +!! +!! character(len=*),intent(in) :: str(:) +!! character(len=*),intent(in),optional :: sep +!! logical,intent(in),optional :: trm +!! character(len=*),intent(in),optional :: right +!! character(len=*),intent(in),optional :: left +!! character(len=*),intent(in),optional :: start +!! character(len=*),intent(in),optional :: end +!! character(len=:),allocatable :: string +!! +!!##DESCRIPTION +!! JOIN(3f) appends the elements of a CHARACTER array into a single +!! CHARACTER variable, with elements 1 to N joined from left to right. +!! By default each element is trimmed of trailing spaces and the +!! default separator is a null string. +!! +!!##OPTIONS +!! STR(:) array of CHARACTER variables to be joined +!! SEP separator string to place between each variable. defaults +!! to a null string. +!! LEFT string to place at left of each element +!! RIGHT string to place at right of each element +!! START prefix string +!! END suffix string +!! TRM option to trim each element of STR of trailing +!! spaces. Defaults to .TRUE. +!! +!!##RESULT +!! STRING CHARACTER variable composed of all of the elements of STR() +!! appended together with the optional separator SEP placed +!! between the elements. +!! +!!##EXAMPLE +!! +!! Sample program: +!! +!! program demo_join +!! use fpm_strings, only: join +!! implicit none +!! character(len=:),allocatable :: s(:) +!! character(len=:),allocatable :: out +!! integer :: i +!! s=[character(len=10) :: 'United',' we',' stand,', & +!! & ' divided',' we fall.'] +!! out=join(s) +!! write(*,'(a)') out +!! write(*,'(a)') join(s,trm=.false.) +!! write(*,'(a)') (join(s,trm=.false.,sep='|'),i=1,3) +!! write(*,'(a)') join(s,sep='<>') +!! write(*,'(a)') join(s,sep=';',left='[',right=']') +!! write(*,'(a)') join(s,left='[',right=']') +!! write(*,'(a)') join(s,left='>>') +!! end program demo_join +!! +!! Expected output: +!! +!! United we stand, divided we fall. +!! United we stand, divided we fall. +!! United | we | stand, | divided | we fall. +!! United | we | stand, | divided | we fall. +!! United | we | stand, | divided | we fall. +!! United<> we<> stand,<> divided<> we fall. +!! [United];[ we];[ stand,];[ divided];[ we fall.] +!! [United][ we][ stand,][ divided][ we fall.] +!! >>United>> we>> stand,>> divided>> we fall. +!! +!!##AUTHOR +!! John S. Urban +!! +!!##LICENSE +!! Public Domain + +! @(#)join(3f): append an array of character variables with specified separator into a single CHARACTER variable + +character(len=*),intent(in) :: str(:) +character(len=*),intent(in),optional :: sep +character(len=*),intent(in),optional :: right +character(len=*),intent(in),optional :: left +character(len=*),intent(in),optional :: start +character(len=*),intent(in),optional :: end +logical,intent(in),optional :: trm +character(len=:),allocatable :: string +integer :: i +logical :: trm_local +character(len=:),allocatable :: sep_local +character(len=:),allocatable :: left_local +character(len=:),allocatable :: right_local if(present(sep))then ; sep_local=sep ; else ; sep_local='' ; endif if(present(trm))then ; trm_local=trm ; else ; trm_local=.true. ; endif @@ -477,19 +487,26 @@ character(len=:),allocatable :: sep_local, left_local, right_local if(present(right))then ; right_local=right ; else ; right_local='' ; endif string='' - do i = 1,size(str) + do i = 1,size(str)-1 if(trm_local)then string=string//left_local//trim(str(i))//right_local//sep_local else string=string//left_local//str(i)//right_local//sep_local endif enddo + if(trm_local)then + string=string//left_local//trim(str(i))//right_local + else + string=string//left_local//str(i)//right_local + endif + if(present(start))string=start//string + if(present(end))string=string//end end function join function glob(tame,wild) !> !!##NAME -!! glob(3f) - [M_strings:COMPARE] compare given string for match to +!! glob(3f) - [fpm_strings:COMPARE] compare given string for match to !! pattern which may contain wildcard characters !! (LICENSE:PD) !! @@ -687,7 +704,7 @@ function glob(tame,wild) !! ! matching routines. !! ! !! function test(tame, wild, bExpectedResult) result(bpassed) -!! use M_strings, only : glob +!! use fpm_strings, only : glob !! character(len=*) :: tame !! character(len=*) :: wild !! logical :: bExpectedResult @@ -722,7 +739,7 @@ function glob(tame,wild) !!##LICENSE !! Public Domain -! ident_6="@(#)M_strings::glob(3f): function compares text strings, one of which can have wildcards ('*' or '?')." +! @(#)fpm_strings::glob(3f): function compares text strings, one of which can have wildcards ('*' or '?'). logical :: glob character(len=*) :: tame ! A string without wildcards |