Skip to content

Commit ab57ec6

Browse files
committed
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).
1 parent 90e1409 commit ab57ec6

File tree

3 files changed

+144
-121
lines changed

3 files changed

+144
-121
lines changed

fpm/src/fpm.f90

Lines changed: 20 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
module fpm
2-
use fpm_strings, only: string_t, operator(.in.), glob
2+
use fpm_strings, only: string_t, operator(.in.), glob, join
33
use fpm_backend, only: build_package
44
use fpm_command_line, only: fpm_build_settings, fpm_new_settings, &
55
fpm_run_settings, fpm_install_settings, fpm_test_settings
@@ -221,6 +221,7 @@ subroutine cmd_run(settings,test)
221221
type(build_target_t), pointer :: exe_target
222222
type(srcfile_t), pointer :: exe_source
223223
integer :: run_scope
224+
character(len=:),allocatable :: line
224225

225226
call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
226227
if (allocated(error)) then
@@ -299,16 +300,19 @@ subroutine cmd_run(settings,test)
299300
if ( any(.not.found) .or. &
300301
& (size(settings%name).eq.0 .and. size(executables).gt.1 .and. .not.test) .and.&
301302
& .not.settings%list) then
302-
if(any(.not.found))then
303-
write(stderr,'(A)',advance="no")'fpm::run<ERROR> specified names '
304-
do j=1,size(settings%name)
305-
if (.not.found(j)) write(stderr,'(A)',advance="no") '"'//trim(settings%name(j))//'" '
306-
end do
307-
write(stderr,'(A)') 'not found.'
308-
write(stderr,*)
309-
else if(settings%verbose)then
310-
write(stderr,'(A)',advance="yes")'<INFO>when more than one executable is available'
311-
write(stderr,'(A)',advance="yes")' program names must be specified.'
303+
line=join(settings%name)
304+
if(line.ne.'.'.and. line.ne.'..')then ! do not report these special strings
305+
if(any(.not.found))then
306+
write(stderr,'(A)',advance="no")'fpm::run<ERROR> specified names '
307+
do j=1,size(settings%name)
308+
if (.not.found(j)) write(stderr,'(A)',advance="no") '"'//trim(settings%name(j))//'" '
309+
end do
310+
write(stderr,'(A)') 'not found.'
311+
write(stderr,*)
312+
else if(settings%verbose)then
313+
write(stderr,'(A)',advance="yes")'<INFO>when more than one executable is available'
314+
write(stderr,'(A)',advance="yes")' program names must be specified.'
315+
endif
312316
endif
313317

314318
j = 1
@@ -336,7 +340,11 @@ subroutine cmd_run(settings,test)
336340
end do
337341

338342
write(stderr,*)
339-
stop 1
343+
if(line.eq.'.' .or. line.eq.' '.or. line.eq.'..')then ! do not report these special strings
344+
stop
345+
else
346+
stop 1
347+
endif
340348

341349
end if
342350

fpm/src/fpm_command_line.f90

Lines changed: 17 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -152,7 +152,6 @@ subroutine get_command_line_settings(cmd_settings)
152152
call set_args('&
153153
& --target " " &
154154
& --list F &
155-
& --all F &
156155
& --release F&
157156
& --example F&
158157
& --runner " " &
@@ -172,9 +171,6 @@ subroutine get_command_line_settings(cmd_settings)
172171
call split(sget('target'),tnames,delimiters=' ,:')
173172
names=[character(len=max(len(names),len(tnames))) :: names,tnames]
174173
endif
175-
if(lget('all'))then
176-
names=[character(len=max(len(names),1)) :: names,'*']
177-
endif
178174

179175
allocate(fpm_run_settings :: cmd_settings)
180176
val_runner=sget('runner')
@@ -505,7 +501,7 @@ subroutine set_help()
505501
' [--full|--bare][--backfill] ', &
506502
' update [NAME(s)] [--fetch-only] [--clean] [--verbose] ', &
507503
' list [--list] ', &
508-
' run [[--target] NAME(s)|--all] [--example] [--release] [--runner "CMD"] ', &
504+
' run [[--target] NAME(s) [--example] [--release] [--runner "CMD"] ', &
509505
' [--compiler COMPILER_NAME] [--list] [-- ARGS] ', &
510506
' test [[--target] NAME(s)] [--release] [--runner "CMD"] [--list] ', &
511507
' [--compiler COMPILER_NAME] [-- ARGS] ', &
@@ -618,7 +614,7 @@ subroutine set_help()
618614
' new NAME [[--lib|--src] [--app] [--test] [--example]]| ', &
619615
' [--full|--bare][--backfill] ', &
620616
' update [NAME(s)] [--fetch-only] [--clean] ', &
621-
' run [[--target] NAME(s)|--all] [--release] [--list] [--example] ', &
617+
' run [[--target] NAME(s)] [--release] [--list] [--example] ', &
622618
' [--runner "CMD"] [--compiler COMPILER_NAME] [-- ARGS] ', &
623619
' test [[--target] NAME(s)] [--release] [--list] ', &
624620
' [--runner "CMD"] [--compiler COMPILER_NAME] [-- ARGS] ', &
@@ -690,7 +686,7 @@ subroutine set_help()
690686
' run(1) - the fpm(1) subcommand to run project applications ', &
691687
' ', &
692688
'SYNOPSIS ', &
693-
' fpm run [[--target] NAME(s)|-all][--release][--compiler COMPILER_NAME]', &
689+
' fpm run [[--target] NAME(s)[--release][--compiler COMPILER_NAME] ', &
694690
' [--runner "CMD"] [--example] [--list][-- ARGS] ', &
695691
' ', &
696692
' fpm run --help|--version ', &
@@ -703,15 +699,16 @@ subroutine set_help()
703699
' are automatically rebuilt before being run if they are out of date. ', &
704700
' ', &
705701
'OPTIONS ', &
706-
' --target NAME(s) list of specific application names to execute. ', &
707-
' No name is required if only one application exists. ', &
708-
' If no name is supplied and more than one candidate ', &
709-
' exists or a name has no match a list is produced ', &
710-
' and fpm(1) exits. ', &
711-
' Simple "globbing" is supported where "?" represents ', &
712-
' any single character and "*" represents any string. ', &
713-
' Therefore a quoted asterisk ''*'' runs all programs. ', &
714-
' --all An alias for "--target ''*''". All targets are selected. ', &
702+
' --target NAME(s) list of specific application names to execute. ', &
703+
' No name is required if only one application exists.', &
704+
' If no name is supplied and more than one candidate ', &
705+
' exists or a name has no match a list is produced ', &
706+
' and fpm(1) exits. ', &
707+
' Simple "globbing" is supported where "?" represents', &
708+
' any single character and "*" represents any string. ', &
709+
' Therefore a quoted asterisk ''*'' runs all programs. ', &
710+
' The special string "." also causes all targets to ', &
711+
' be listed, even if only a single target exists. ', &
715712
' --example Run example programs instead of applications. ', &
716713
' --release selects the optimized build instead of the debug build. ', &
717714
' --compiler COMPILER_NAME Specify a compiler name. The default is ', &
@@ -726,10 +723,11 @@ subroutine set_help()
726723
' arguments are passed to all program names specified. ', &
727724
' ', &
728725
'EXAMPLES ', &
729-
' fpm(1) - run project applications: ', &
726+
' fpm(1) - run or display project applications: ', &
730727
' ', &
731-
' # run all default programs in /app or as specified in "fpm.toml" ', &
732-
' fpm run --all ', &
728+
' fpm run # run a target when only one exists or list targets ', &
729+
' fpm run ''*'' # run all targets ', &
730+
' fpm run . # list all targets, running nothing ', &
733731
' ', &
734732
' # run default program built or to be built with the compiler command ', &
735733
' # "f90". If more than one app exists a list displays and target names', &

fpm/src/fpm_strings.f90

Lines changed: 107 additions & 90 deletions
Original file line numberDiff line numberDiff line change
@@ -383,113 +383,130 @@ subroutine resize_string(list, n)
383383

384384
end subroutine resize_string
385385

386-
pure function join(str,sep,trm,left,right) result (string)
387-
388-
!> M_strings::join(3f): append an array of character variables with specified separator into a single CHARACTER variable
389-
!>
390-
!>##NAME
391-
!> join(3f) - [M_strings:EDITING] append CHARACTER variable array into
392-
!> a single CHARACTER variable with specified separator
393-
!> (LICENSE:PD)
394-
!>
395-
!>##SYNOPSIS
396-
!>
397-
!> pure function join(str,sep,trm,left,right) result (string)
398-
!>
399-
!> character(len=*),intent(in) :: str(:)
400-
!> character(len=*),intent(in),optional :: sep
401-
!> logical,intent(in),optional :: trm
402-
!> character(len=*),intent(in),optional :: right
403-
!> character(len=*),intent(in),optional :: left
404-
!> character(len=:),allocatable :: string
405-
!>
406-
!>##DESCRIPTION
407-
!> JOIN(3f) appends the elements of a CHARACTER array into a single
408-
!> CHARACTER variable, with elements 1 to N joined from left to right.
409-
!> By default each element is trimmed of trailing spaces and the
410-
!> default separator is a null string.
411-
!>
412-
!>##OPTIONS
413-
!> STR(:) array of CHARACTER variables to be joined
414-
!> SEP separator string to place between each variable. defaults
415-
!> to a null string.
416-
!> LEFT string to place at left of each element
417-
!> RIGHT string to place at right of each element
418-
!> TRM option to trim each element of STR of trailing
419-
!> spaces. Defaults to .TRUE.
420-
!>
421-
!>##RESULT
422-
!> STRING CHARACTER variable composed of all of the elements of STR()
423-
!> appended together with the optional separator SEP placed
424-
!> between the elements and optional left and right elements.
425-
!>
426-
!>##EXAMPLE
386+
pure function join(str,sep,trm,left,right,start,end) result (string)
427387
!>
428-
!> Sample program:
429-
!>
430-
!> program demo_join
431-
!> use M_strings, only: join
432-
!> implicit none
433-
!> character(len=:),allocatable :: s(:)
434-
!> character(len=:),allocatable :: out
435-
!> integer :: i
436-
!> s=[character(len=10) :: 'United',' we',' stand,', &
437-
!> & ' divided',' we fall.']
438-
!> out=join(s)
439-
!> write(*,'(a)') out
440-
!> write(*,'(a)') join(s,trm=.false.)
441-
!> write(*,'(a)') (join(s,trm=.false.,sep='|'),i=1,3)
442-
!> write(*,'(a)') join(s,sep='<>')
443-
!> write(*,'(a)') join(s,sep=';',left='[',right=']')
444-
!> write(*,'(a)') join(s,left='[',right=']')
445-
!> write(*,'(a)') join(s,left='>>')
446-
!> end program demo_join
447-
!>
448-
!> Expected output:
449-
!>
450-
!> United we stand, divided we fall.
451-
!> United we stand, divided we fall.
452-
!> United | we | stand, | divided | we fall. |
453-
!> United | we | stand, | divided | we fall. |
454-
!> United | we | stand, | divided | we fall. |
455-
!> United<> we<> stand,<> divided<> we fall.<>
456-
!> [United];[ we];[ stand,];[ divided];[ we fall.];
457-
!> [United][ we][ stand,][ divided][ we fall.]
458-
!> >>United>> we>> stand,>> divided>> we fall.
459-
!>
460-
!>##AUTHOR
461-
!> John S. Urban
462-
!>
463-
!>##LICENSE
464-
!> Public Domain
465-
466-
character(len=*),intent(in) :: str(:)
467-
character(len=*),intent(in),optional :: sep, right, left
468-
logical,intent(in),optional :: trm
469-
character(len=:),allocatable :: string
470-
integer :: i
471-
logical :: trm_local
472-
character(len=:),allocatable :: sep_local, left_local, right_local
388+
!!##NAME
389+
!! join(3f) - [fpm_strings:EDITING] append CHARACTER variable array into
390+
!! a single CHARACTER variable with specified separator
391+
!! (LICENSE:PD)
392+
!!
393+
!!##SYNOPSIS
394+
!!
395+
!! pure function join(str,sep,trm,left,right,start,end) result (string)
396+
!!
397+
!! character(len=*),intent(in) :: str(:)
398+
!! character(len=*),intent(in),optional :: sep
399+
!! logical,intent(in),optional :: trm
400+
!! character(len=*),intent(in),optional :: right
401+
!! character(len=*),intent(in),optional :: left
402+
!! character(len=*),intent(in),optional :: start
403+
!! character(len=*),intent(in),optional :: end
404+
!! character(len=:),allocatable :: string
405+
!!
406+
!!##DESCRIPTION
407+
!! JOIN(3f) appends the elements of a CHARACTER array into a single
408+
!! CHARACTER variable, with elements 1 to N joined from left to right.
409+
!! By default each element is trimmed of trailing spaces and the
410+
!! default separator is a null string.
411+
!!
412+
!!##OPTIONS
413+
!! STR(:) array of CHARACTER variables to be joined
414+
!! SEP separator string to place between each variable. defaults
415+
!! to a null string.
416+
!! LEFT string to place at left of each element
417+
!! RIGHT string to place at right of each element
418+
!! START prefix string
419+
!! END suffix string
420+
!! TRM option to trim each element of STR of trailing
421+
!! spaces. Defaults to .TRUE.
422+
!!
423+
!!##RESULT
424+
!! STRING CHARACTER variable composed of all of the elements of STR()
425+
!! appended together with the optional separator SEP placed
426+
!! between the elements.
427+
!!
428+
!!##EXAMPLE
429+
!!
430+
!! Sample program:
431+
!!
432+
!! program demo_join
433+
!! use fpm_strings, only: join
434+
!! implicit none
435+
!! character(len=:),allocatable :: s(:)
436+
!! character(len=:),allocatable :: out
437+
!! integer :: i
438+
!! s=[character(len=10) :: 'United',' we',' stand,', &
439+
!! & ' divided',' we fall.']
440+
!! out=join(s)
441+
!! write(*,'(a)') out
442+
!! write(*,'(a)') join(s,trm=.false.)
443+
!! write(*,'(a)') (join(s,trm=.false.,sep='|'),i=1,3)
444+
!! write(*,'(a)') join(s,sep='<>')
445+
!! write(*,'(a)') join(s,sep=';',left='[',right=']')
446+
!! write(*,'(a)') join(s,left='[',right=']')
447+
!! write(*,'(a)') join(s,left='>>')
448+
!! end program demo_join
449+
!!
450+
!! Expected output:
451+
!!
452+
!! United we stand, divided we fall.
453+
!! United we stand, divided we fall.
454+
!! United | we | stand, | divided | we fall.
455+
!! United | we | stand, | divided | we fall.
456+
!! United | we | stand, | divided | we fall.
457+
!! United<> we<> stand,<> divided<> we fall.
458+
!! [United];[ we];[ stand,];[ divided];[ we fall.]
459+
!! [United][ we][ stand,][ divided][ we fall.]
460+
!! >>United>> we>> stand,>> divided>> we fall.
461+
!!
462+
!!##AUTHOR
463+
!! John S. Urban
464+
!!
465+
!!##LICENSE
466+
!! Public Domain
467+
468+
! @(#)join(3f): append an array of character variables with specified separator into a single CHARACTER variable
469+
470+
character(len=*),intent(in) :: str(:)
471+
character(len=*),intent(in),optional :: sep
472+
character(len=*),intent(in),optional :: right
473+
character(len=*),intent(in),optional :: left
474+
character(len=*),intent(in),optional :: start
475+
character(len=*),intent(in),optional :: end
476+
logical,intent(in),optional :: trm
477+
character(len=:),allocatable :: string
478+
integer :: i
479+
logical :: trm_local
480+
character(len=:),allocatable :: sep_local
481+
character(len=:),allocatable :: left_local
482+
character(len=:),allocatable :: right_local
473483

474484
if(present(sep))then ; sep_local=sep ; else ; sep_local='' ; endif
475485
if(present(trm))then ; trm_local=trm ; else ; trm_local=.true. ; endif
476486
if(present(left))then ; left_local=left ; else ; left_local='' ; endif
477487
if(present(right))then ; right_local=right ; else ; right_local='' ; endif
478488

479489
string=''
480-
do i = 1,size(str)
490+
do i = 1,size(str)-1
481491
if(trm_local)then
482492
string=string//left_local//trim(str(i))//right_local//sep_local
483493
else
484494
string=string//left_local//str(i)//right_local//sep_local
485495
endif
486496
enddo
497+
if(trm_local)then
498+
string=string//left_local//trim(str(i))//right_local
499+
else
500+
string=string//left_local//str(i)//right_local
501+
endif
502+
if(present(start))string=start//string
503+
if(present(end))string=string//end
487504
end function join
488505

489506
function glob(tame,wild)
490507
!>
491508
!!##NAME
492-
!! glob(3f) - [M_strings:COMPARE] compare given string for match to
509+
!! glob(3f) - [fpm_strings:COMPARE] compare given string for match to
493510
!! pattern which may contain wildcard characters
494511
!! (LICENSE:PD)
495512
!!
@@ -687,7 +704,7 @@ function glob(tame,wild)
687704
!! ! matching routines.
688705
!! !
689706
!! function test(tame, wild, bExpectedResult) result(bpassed)
690-
!! use M_strings, only : glob
707+
!! use fpm_strings, only : glob
691708
!! character(len=*) :: tame
692709
!! character(len=*) :: wild
693710
!! logical :: bExpectedResult
@@ -722,7 +739,7 @@ function glob(tame,wild)
722739
!!##LICENSE
723740
!! Public Domain
724741

725-
! ident_6="@(#)M_strings::glob(3f): function compares text strings, one of which can have wildcards ('*' or '?')."
742+
! @(#)fpm_strings::glob(3f): function compares text strings, one of which can have wildcards ('*' or '?').
726743

727744
logical :: glob
728745
character(len=*) :: tame ! A string without wildcards

0 commit comments

Comments
 (0)