Skip to content

Commit b406adf

Browse files
committed
--all is back; --list is compact
1 parent 59837ec commit b406adf

File tree

3 files changed

+86
-56
lines changed

3 files changed

+86
-56
lines changed

fpm/src/fpm.f90

Lines changed: 41 additions & 35 deletions
Original file line numberDiff line numberDiff line change
@@ -210,8 +210,7 @@ subroutine cmd_run(settings,test)
210210
class(fpm_run_settings), intent(in) :: settings
211211
logical, intent(in) :: test
212212

213-
integer, parameter :: LINE_WIDTH = 80
214-
integer :: i, j, col_width, nCol
213+
integer :: i, j, col_width
215214
logical :: found(size(settings%name))
216215
type(error_t), allocatable :: error
217216
type(package_config_t) :: package
@@ -222,6 +221,7 @@ subroutine cmd_run(settings,test)
222221
type(srcfile_t), pointer :: exe_source
223222
integer :: run_scope
224223
character(len=:),allocatable :: line
224+
logical :: toomany
225225

226226
call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
227227
if (allocated(error)) then
@@ -297,8 +297,11 @@ subroutine cmd_run(settings,test)
297297

298298
! Check all names are valid
299299
! or no name and found more than one file
300-
if ( any(.not.found) .or. &
301-
& (size(settings%name).eq.0 .and. size(executables).gt.1 .and. .not.test) .and.&
300+
toomany= size(settings%name).eq.0 .and. size(executables).gt.1
301+
if ( any(.not.found) &
302+
& .or. &
303+
& ( (toomany .and. .not.test) .or. (toomany .and. settings%runner .ne. '') ) &
304+
& .and. &
302305
& .not.settings%list) then
303306
line=join(settings%name)
304307
if(line.ne.'.')then ! do not report these special strings
@@ -315,6 +318,39 @@ subroutine cmd_run(settings,test)
315318
endif
316319
endif
317320

321+
call compact_list()
322+
323+
if(line.eq.'.' .or. line.eq.' ')then ! do not report these special strings
324+
stop
325+
else
326+
stop 1
327+
endif
328+
329+
end if
330+
331+
call build_package(model)
332+
333+
if (settings%list) then
334+
call compact_list()
335+
else
336+
337+
do i=1,size(executables)
338+
if (exists(executables(i)%s)) then
339+
if(settings%runner .ne. ' ')then
340+
call run(settings%runner//' '//executables(i)%s//" "//settings%args,echo=settings%verbose)
341+
else
342+
call run(executables(i)%s//" "//settings%args,echo=settings%verbose)
343+
endif
344+
else
345+
write(stderr,*)'fpm::run<ERROR>',executables(i)%s,' not found'
346+
stop 1
347+
end if
348+
end do
349+
endif
350+
contains
351+
subroutine compact_list()
352+
integer, parameter :: LINE_WIDTH = 80
353+
integer :: i, j, nCol
318354
j = 1
319355
nCol = LINE_WIDTH/col_width
320356
write(stderr,*) 'Available names:'
@@ -334,40 +370,10 @@ subroutine cmd_run(settings,test)
334370
j = j + 1
335371

336372
end if
337-
338373
end if
339-
340374
end do
341-
342375
write(stderr,*)
343-
if(line.eq.'.' .or. line.eq.' ')then ! do not report these special strings
344-
stop
345-
else
346-
stop 1
347-
endif
348-
349-
end if
350-
351-
call build_package(model)
352-
353-
do i=1,size(executables)
354-
if (settings%list) then
355-
write(stderr,*) executables(i)%s
356-
else
357-
358-
if (exists(executables(i)%s)) then
359-
if(settings%runner .ne. ' ')then
360-
call run(settings%runner//' '//executables(i)%s//" "//settings%args)
361-
else
362-
call run(executables(i)%s//" "//settings%args)
363-
endif
364-
else
365-
write(stderr,*)'fpm::run<ERROR>',executables(i)%s,' not found'
366-
stop 1
367-
end if
368-
369-
end if
370-
end do
376+
end subroutine compact_list
371377

372378
end subroutine cmd_run
373379

fpm/src/fpm_command_line.f90

Lines changed: 34 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -152,6 +152,7 @@ subroutine get_command_line_settings(cmd_settings)
152152
call set_args('&
153153
& --target " " &
154154
& --list F &
155+
& --all F &
155156
& --release F&
156157
& --example F&
157158
& --runner " " &
@@ -167,11 +168,17 @@ subroutine get_command_line_settings(cmd_settings)
167168
names=[character(len=len(names)) :: ]
168169
endif
169170

171+
170172
if(specified('target') )then
171173
call split(sget('target'),tnames,delimiters=' ,:')
172174
names=[character(len=max(len(names),len(tnames))) :: names,tnames]
173175
endif
174176

177+
! convert --all to '*'
178+
if(lget('all'))then
179+
names=[character(len=max(len(names),1)) :: names,'*' ]
180+
endif
181+
175182
! convert special string '..' to equivalent (shorter) '*'
176183
! to allow for a string that does not require shift-key and quoting
177184
do i=1,size(names)
@@ -180,6 +187,7 @@ subroutine get_command_line_settings(cmd_settings)
180187

181188
allocate(fpm_run_settings :: cmd_settings)
182189
val_runner=sget('runner')
190+
if(specified('runner') .and. val_runner.eq.'')val_runner='echo'
183191
cmd_settings=fpm_run_settings(&
184192
& args=remaining,&
185193
& build_name=val_build,&
@@ -389,6 +397,7 @@ subroutine get_command_line_settings(cmd_settings)
389397

390398
allocate(fpm_test_settings :: cmd_settings)
391399
val_runner=sget('runner')
400+
if(specified('runner') .and. val_runner.eq.'')val_runner='echo'
392401
cmd_settings=fpm_test_settings(&
393402
& args=remaining, &
394403
& build_name=val_build, &
@@ -513,7 +522,7 @@ subroutine set_help()
513522
' [--full|--bare][--backfill] ', &
514523
' update [NAME(s)] [--fetch-only] [--clean] [--verbose] ', &
515524
' list [--list] ', &
516-
' run [[--target] NAME(s) [--example] [--release] [--runner "CMD"] ', &
525+
' run [[--target] NAME(s) [--example] [--release] [-all] [--runner "CMD"] ', &
517526
' [--compiler COMPILER_NAME] [--list] [-- ARGS] ', &
518527
' test [[--target] NAME(s)] [--release] [--runner "CMD"] [--list] ', &
519528
' [--compiler COMPILER_NAME] [-- ARGS] ', &
@@ -541,7 +550,8 @@ subroutine set_help()
541550
'OPTION ', &
542551
' --runner ''CMD'' quoted command used to launch the fpm(1) executables. ', &
543552
' Available for both the "run" and "test" subcommands. ', &
544-
' ', &
553+
' If the keyword is specified without a value the default command ', &
554+
' is "echo". ', &
545555
' -- SUFFIX_OPTIONS additional options to suffix the command CMD and executable ', &
546556
' file names with. ', &
547557
'EXAMPLES ', &
@@ -626,7 +636,7 @@ subroutine set_help()
626636
' new NAME [[--lib|--src] [--app] [--test] [--example]]| ', &
627637
' [--full|--bare][--backfill] ', &
628638
' update [NAME(s)] [--fetch-only] [--clean] ', &
629-
' run [[--target] NAME(s)] [--release] [--list] [--example] ', &
639+
' run [[--target] NAME(s)] [--release] [--list] [--example] [-all] ', &
630640
' [--runner "CMD"] [--compiler COMPILER_NAME] [-- ARGS] ', &
631641
' test [[--target] NAME(s)] [--release] [--list] ', &
632642
' [--runner "CMD"] [--compiler COMPILER_NAME] [-- ARGS] ', &
@@ -699,7 +709,7 @@ subroutine set_help()
699709
' ', &
700710
'SYNOPSIS ', &
701711
' fpm run [[--target] NAME(s)[--release][--compiler COMPILER_NAME] ', &
702-
' [--runner "CMD"] [--example] [--list][-- ARGS] ', &
712+
' [--runner "CMD"] [--example] [--list] [--all] [-- ARGS] ', &
703713
' ', &
704714
' fpm run --help|--version ', &
705715
' ', &
@@ -711,17 +721,17 @@ subroutine set_help()
711721
' are automatically rebuilt before being run if they are out of date. ', &
712722
' ', &
713723
'OPTIONS ', &
714-
' --target NAME(s) list of specific application names to execute. ', &
715-
' No name is required if only one target exists. ', &
716-
' If no name is supplied and more than one candidate ', &
717-
' exists or a name has no match a list is produced ', &
718-
' and fpm(1) exits. ', &
719-
' Basic "globbing" is supported where "?" represents', &
724+
' --target NAME(s) list of application names to execute. No name is ', &
725+
' required if only one target exists. If no name is ', &
726+
' supplied and more than one candidate exists or a ', &
727+
' name has no match a list is produced and fpm(1) ', &
728+
' exits. ', &
729+
' ', &
730+
' Basic "globbing" is supported where "?" represents ', &
720731
' any single character and "*" represents any string. ', &
721-
' The special string "." causes all targets to ', &
722-
' be listed, even if only a single target exists. ', &
723-
' The special string ".." causes all targets to ', &
724-
' be executed. ', &
732+
' Note The glob string normally needs quoted to ', &
733+
' the special characters from shell expansion. ', &
734+
' --all Run all examples or applications. An alias for --target ''*''. ', &
725735
' --example Run example programs instead of applications. ', &
726736
' --release selects the optimized build instead of the debug build. ', &
727737
' --compiler COMPILER_NAME Specify a compiler name. The default is ', &
@@ -738,9 +748,9 @@ subroutine set_help()
738748
'EXAMPLES ', &
739749
' fpm(1) - run or display project applications: ', &
740750
' ', &
741-
' fpm run # run a target when only one exists or list targets ', &
742-
' fpm run . # list all targets, running nothing ', &
743-
' fpm run .. # run all targets, no matter how many there are ', &
751+
' fpm run # run a target when only one exists or list targets ', &
752+
' fpm run --list # list all targets, running nothing. ', &
753+
' fpm run --all # run all targets, no matter how many there are. ', &
744754
' ', &
745755
' # run default program built or to be built with the compiler command ', &
746756
' # "f90". If more than one app exists a list displays and target names', &
@@ -930,9 +940,9 @@ subroutine set_help()
930940
' cd myproject # Enter the new directory ', &
931941
' # and run commands such as ', &
932942
' fpm build ', &
933-
' fpm run # run example application program(s) ', &
943+
' fpm run # run lone example application program ', &
934944
' fpm test # run example test program(s) ', &
935-
' fpm run --example # run example program(s) ', &
945+
' fpm run --example # run lone example program ', &
936946
' ', &
937947
' fpm new A --full # create example/ and an annotated fpm.toml as well', &
938948
' fpm new A --bare # create no directories ', &
@@ -956,6 +966,11 @@ subroutine set_help()
956966
' --target NAME(s) optional list of specific test names to execute. ', &
957967
' The default is to run all the tests in test/ ', &
958968
' or the tests listed in the "fpm.toml" file. ', &
969+
' ', &
970+
' Basic "globbing" is supported where "?" represents ', &
971+
' any single character and "*" represents any string. ', &
972+
' Note The glob string normally needs quoted to ', &
973+
' protect the special characters from shell expansion.', &
959974
' --release selects the optimized build instead of the debug ', &
960975
' build. ', &
961976
' --compiler COMPILER_NAME Specify a compiler name. The default is ', &

fpm/src/fpm_environment.f90

Lines changed: 11 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -117,10 +117,19 @@ logical function os_is_unix(os) result(unix)
117117
unix = os /= OS_WINDOWS
118118
end function os_is_unix
119119

120-
subroutine run(cmd)
120+
subroutine run(cmd,echo)
121121
character(len=*), intent(in) :: cmd
122+
logical,intent(in),optional :: echo
123+
logical :: echo_local
122124
integer :: stat
123-
print *, '+ ', cmd
125+
126+
if(present(echo))then
127+
echo_local=echo
128+
else
129+
echo_local=.true.
130+
endif
131+
if(echo_local) print *, '+ ', cmd
132+
124133
call execute_command_line(cmd, exitstat=stat)
125134
if (stat /= 0) then
126135
print *, 'Command failed'

0 commit comments

Comments
 (0)