Skip to content

Commit 5546685

Browse files
authored
Merge pull request #370 from urbanjost/multiExe
Changed behavior for run subcommand per @lkedwards suggestions
2 parents 72b960b + 96a8619 commit 5546685

File tree

4 files changed

+585
-160
lines changed

4 files changed

+585
-160
lines changed

fpm/src/fpm.f90

Lines changed: 72 additions & 37 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.)
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
@@ -213,8 +213,7 @@ subroutine cmd_run(settings,test)
213213
class(fpm_run_settings), intent(in) :: settings
214214
logical, intent(in) :: test
215215

216-
integer, parameter :: LINE_WIDTH = 80
217-
integer :: i, j, col_width, nCol
216+
integer :: i, j, col_width
218217
logical :: found(size(settings%name))
219218
type(error_t), allocatable :: error
220219
type(package_config_t) :: package
@@ -224,6 +223,8 @@ subroutine cmd_run(settings,test)
224223
type(build_target_t), pointer :: exe_target
225224
type(srcfile_t), pointer :: exe_source
226225
integer :: run_scope
226+
character(len=:),allocatable :: line
227+
logical :: toomany
227228

228229
call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
229230
if (allocated(error)) then
@@ -269,7 +270,7 @@ subroutine cmd_run(settings,test)
269270

270271
do j=1,size(settings%name)
271272

272-
if (trim(settings%name(j))==exe_source%exe_name) then
273+
if (glob(trim(exe_source%exe_name),trim(settings%name(j)))) then
273274

274275
found(j) = .true.
275276
exe_cmd%s = exe_target%output_file
@@ -298,15 +299,61 @@ subroutine cmd_run(settings,test)
298299
end if
299300

300301
! Check all names are valid
301-
if (any(.not.found)) then
302+
! or no name and found more than one file
303+
toomany= size(settings%name).eq.0 .and. size(executables).gt.1
304+
if ( any(.not.found) &
305+
& .or. &
306+
& ( (toomany .and. .not.test) .or. (toomany .and. settings%runner .ne. '') ) &
307+
& .and. &
308+
& .not.settings%list) then
309+
line=join(settings%name)
310+
if(line.ne.'.')then ! do not report these special strings
311+
if(any(.not.found))then
312+
write(stderr,'(A)',advance="no")'fpm::run<ERROR> specified names '
313+
do j=1,size(settings%name)
314+
if (.not.found(j)) write(stderr,'(A)',advance="no") '"'//trim(settings%name(j))//'" '
315+
end do
316+
write(stderr,'(A)') 'not found.'
317+
write(stderr,*)
318+
else if(settings%verbose)then
319+
write(stderr,'(A)',advance="yes")'<INFO>when more than one executable is available'
320+
write(stderr,'(A)',advance="yes")' program names must be specified.'
321+
endif
322+
endif
302323

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,*)
324+
call compact_list_all()
325+
326+
if(line.eq.'.' .or. line.eq.' ')then ! do not report these special strings
327+
stop
328+
else
329+
stop 1
330+
endif
331+
332+
end if
333+
334+
call build_package(model)
335+
336+
if (settings%list) then
337+
call compact_list()
338+
else
309339

340+
do i=1,size(executables)
341+
if (exists(executables(i)%s)) then
342+
if(settings%runner .ne. ' ')then
343+
call run(settings%runner//' '//executables(i)%s//" "//settings%args,echo=settings%verbose)
344+
else
345+
call run(executables(i)%s//" "//settings%args,echo=settings%verbose)
346+
endif
347+
else
348+
write(stderr,*)'fpm::run<ERROR>',executables(i)%s,' not found'
349+
stop 1
350+
end if
351+
end do
352+
endif
353+
contains
354+
subroutine compact_list_all()
355+
integer, parameter :: LINE_WIDTH = 80
356+
integer :: i, j, nCol
310357
j = 1
311358
nCol = LINE_WIDTH/col_width
312359
write(stderr,*) 'Available names:'
@@ -326,36 +373,24 @@ subroutine cmd_run(settings,test)
326373
j = j + 1
327374

328375
end if
329-
330376
end if
331-
332377
end do
333-
334378
write(stderr,*)
335-
stop 1
336-
337-
end if
338-
339-
call build_package(model)
340-
341-
do i=1,size(executables)
342-
if (settings%list) then
343-
write(stderr,*) executables(i)%s
344-
else
345-
346-
if (exists(executables(i)%s)) then
347-
if(settings%runner .ne. ' ')then
348-
call run(settings%runner//' '//executables(i)%s//" "//settings%args)
349-
else
350-
call run(executables(i)%s//" "//settings%args)
351-
endif
352-
else
353-
write(stderr,*)'fpm::run<ERROR>',executables(i)%s,' not found'
354-
stop 1
355-
end if
379+
end subroutine compact_list_all
356380

357-
end if
358-
end do
381+
subroutine compact_list()
382+
integer, parameter :: LINE_WIDTH = 80
383+
integer :: i, j, nCol
384+
j = 1
385+
nCol = LINE_WIDTH/col_width
386+
write(stderr,*) 'Matched names:'
387+
do i=1,size(executables)
388+
write(stderr,'(A)',advance=(merge("yes","no ",modulo(j,nCol)==0))) &
389+
& [character(len=col_width) :: basename(executables(i)%s)]
390+
j = j + 1
391+
enddo
392+
write(stderr,*)
393+
end subroutine compact_list
359394

360395
end subroutine cmd_run
361396

fpm/src/fpm_command_line.f90

Lines changed: 70 additions & 33 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,13 +168,26 @@ 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+
182+
! convert special string '..' to equivalent (shorter) '*'
183+
! to allow for a string that does not require shift-key and quoting
184+
do i=1,size(names)
185+
if(names(i).eq.'..')names(i)='*'
186+
enddo
187+
175188
allocate(fpm_run_settings :: cmd_settings)
176189
val_runner=sget('runner')
190+
if(specified('runner') .and. val_runner.eq.'')val_runner='echo'
177191
cmd_settings=fpm_run_settings(&
178192
& args=remaining,&
179193
& build_name=val_build,&
@@ -375,8 +389,15 @@ subroutine get_command_line_settings(cmd_settings)
375389
names=[character(len=max(len(names),len(tnames))) :: names,tnames]
376390
endif
377391

392+
! convert special string '..' to equivalent (shorter) '*'
393+
! to allow for a string that does not require shift-key and quoting
394+
do i=1,size(names)
395+
if(names(i).eq.'..')names(i)='*'
396+
enddo
397+
378398
allocate(fpm_test_settings :: cmd_settings)
379399
val_runner=sget('runner')
400+
if(specified('runner') .and. val_runner.eq.'')val_runner='echo'
380401
cmd_settings=fpm_test_settings(&
381402
& args=remaining, &
382403
& build_name=val_build, &
@@ -501,8 +522,8 @@ subroutine set_help()
501522
' [--full|--bare][--backfill] ', &
502523
' update [NAME(s)] [--fetch-only] [--clean] [--verbose] ', &
503524
' list [--list] ', &
504-
' run [[--target] NAME(s)] [--release] [--runner "CMD"] [--list] [--example] ', &
505-
' [--compiler COMPILER_NAME] [-- ARGS] ', &
525+
' run [[--target] NAME(s) [--example] [--release] [--all] [--runner "CMD"] ', &
526+
' [--compiler COMPILER_NAME] [--list] [-- ARGS] ', &
506527
' test [[--target] NAME(s)] [--release] [--runner "CMD"] [--list] ', &
507528
' [--compiler COMPILER_NAME] [-- ARGS] ', &
508529
' install [--release] [--no-rebuild] [--prefix PATH] [options] ', &
@@ -529,7 +550,8 @@ subroutine set_help()
529550
'OPTION ', &
530551
' --runner ''CMD'' quoted command used to launch the fpm(1) executables. ', &
531552
' Available for both the "run" and "test" subcommands. ', &
532-
' ', &
553+
' If the keyword is specified without a value the default command ', &
554+
' is "echo". ', &
533555
' -- SUFFIX_OPTIONS additional options to suffix the command CMD and executable ', &
534556
' file names with. ', &
535557
'EXAMPLES ', &
@@ -584,7 +606,7 @@ subroutine set_help()
584606
' ', &
585607
'DESCRIPTION ', &
586608
' fpm(1) is a package manager that helps you create Fortran projects ', &
587-
' from source. ', &
609+
' from source -- it automatically determines dependencies! ', &
588610
' ', &
589611
' Most significantly fpm(1) lets you draw upon other fpm(1) packages ', &
590612
' in distributed git(1) repositories as if the packages were a basic ', &
@@ -614,7 +636,7 @@ subroutine set_help()
614636
' new NAME [[--lib|--src] [--app] [--test] [--example]]| ', &
615637
' [--full|--bare][--backfill] ', &
616638
' update [NAME(s)] [--fetch-only] [--clean] ', &
617-
' run [[--target] NAME(s)] [--release] [--list] [--example] ', &
639+
' run [[--target] NAME(s)] [--release] [--list] [--example] [--all] ', &
618640
' [--runner "CMD"] [--compiler COMPILER_NAME] [-- ARGS] ', &
619641
' test [[--target] NAME(s)] [--release] [--list] ', &
620642
' [--runner "CMD"] [--compiler COMPILER_NAME] [-- ARGS] ', &
@@ -686,50 +708,60 @@ subroutine set_help()
686708
' run(1) - the fpm(1) subcommand to run project applications ', &
687709
' ', &
688710
'SYNOPSIS ', &
689-
' fpm run [[--target] NAME(s)][--release][--compiler COMPILER_NAME] ', &
690-
' [--runner "CMD"] [--example] [--list][-- ARGS] ', &
711+
' fpm run [[--target] NAME(s)[--release][--compiler COMPILER_NAME] ', &
712+
' [--runner "CMD"] [--example] [--list] [--all] [-- ARGS] ', &
691713
' ', &
692714
' fpm run --help|--version ', &
693715
' ', &
694716
'DESCRIPTION ', &
695-
' Run applications you have built in your fpm(1) project. ', &
696-
' By default applications specified in as "executable" in your package ', &
697-
' manifest are used, alternatively also demonstration programs under ', &
698-
' "example" can be used with this subcommand. ', &
717+
' Run the applications in your fpm(1) package. By default applications ', &
718+
' in /app or specified as "executable" in your "fpm.toml" manifest are ', &
719+
' used. Alternatively demonstration programs in example/ or specified in', &
720+
' the "example" section in "fpm.toml" can be executed. The applications ', &
721+
' are automatically rebuilt before being run if they are out of date. ', &
699722
' ', &
700723
'OPTIONS ', &
701-
' --target NAME(s) optional list of specific names to execute. ', &
702-
' The default is to run all the applications in app/ ', &
703-
' or the programs listed in the "fpm.toml" file. ', &
704-
' --example run example programs instead of applications ', &
705-
' --release selects the optimized build instead of the debug ', &
706-
' build. ', &
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 ', &
731+
' any single character and "*" represents any string. ', &
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 ''*''. ', &
735+
' --example Run example programs instead of applications. ', &
736+
' --release selects the optimized build instead of the debug build. ', &
707737
' --compiler COMPILER_NAME Specify a compiler name. The default is ', &
708738
' "gfortran" unless set by the environment ', &
709739
' variable FPM_COMPILER. ', &
710740
' --runner CMD A command to prefix the program execution paths with. ', &
711741
' see "fpm help runner" for further details. ', &
712-
' --list list candidates instead of building or running them ', &
713-
' -- ARGS optional arguments to pass to the program(s). ', &
714-
' The same arguments are passed to all names ', &
715-
' specified. ', &
742+
' --list list pathname of candidates instead of running them. Note ', &
743+
' out-of-date candidates will still be rebuilt before being ', &
744+
' listed. ', &
745+
' -- ARGS optional arguments to pass to the program(s). The same ', &
746+
' arguments are passed to all program names specified. ', &
716747
' ', &
717748
'EXAMPLES ', &
718-
' fpm(1) "run" project applications ', &
749+
' fpm(1) - run or display project applications: ', &
719750
' ', &
720-
' # run default programs in /app or as specified in "fpm.toml" ', &
721-
' fpm run ', &
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. ', &
722754
' ', &
723-
' # run default programs in /app or as specified in "fpm.toml" ', &
724-
' # using the compiler command "f90". ', &
755+
' # run default program built or to be built with the compiler command ', &
756+
' # "f90". If more than one app exists a list displays and target names', &
757+
' # are required. ', &
725758
' fpm run --compiler f90 ', &
726759
' ', &
727-
' # run example and demonstration programs instead of the default ', &
728-
' # application programs (specified in "fpm.toml") ', &
729-
' fpm run --example ', &
760+
' # run example programs instead of the application programs. ', &
761+
' fpm run --example ''*'' ', &
730762
' ', &
731763
' # run a specific program and pass arguments to the command ', &
732-
' fpm run mytest -- -x 10 -y 20 --title "my title line" ', &
764+
' fpm run myprog -- -x 10 -y 20 --title "my title line" ', &
733765
' ', &
734766
' # run production version of two applications ', &
735767
' fpm run --target prg1,prg2 --release ', &
@@ -756,7 +788,7 @@ subroutine set_help()
756788
' o src/ for modules and procedure source ', &
757789
' o app/ main program(s) for applications ', &
758790
' o test/ main program(s) and support files for project tests ', &
759-
' o example/ main program(s) for examples and demonstrations ', &
791+
' o example/ main program(s) for example programs ', &
760792
' Changed or new files found are rebuilt. The results are placed in ', &
761793
' the build/ directory. ', &
762794
' ', &
@@ -908,9 +940,9 @@ subroutine set_help()
908940
' cd myproject # Enter the new directory ', &
909941
' # and run commands such as ', &
910942
' fpm build ', &
911-
' fpm run # run example application program(s) ', &
943+
' fpm run # run lone example application program ', &
912944
' fpm test # run example test program(s) ', &
913-
' fpm run --example # run example program(s) ', &
945+
' fpm run --example # run lone example program ', &
914946
' ', &
915947
' fpm new A --full # create example/ and an annotated fpm.toml as well', &
916948
' fpm new A --bare # create no directories ', &
@@ -934,6 +966,11 @@ subroutine set_help()
934966
' --target NAME(s) optional list of specific test names to execute. ', &
935967
' The default is to run all the tests in test/ ', &
936968
' 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.', &
937974
' --release selects the optimized build instead of the debug ', &
938975
' build. ', &
939976
' --compiler COMPILER_NAME Specify a compiler name. The default is ', &

0 commit comments

Comments
 (0)