Skip to content

Commit 86e3d18

Browse files
committed
add runner-args option
1 parent 413073f commit 86e3d18

File tree

4 files changed

+81
-31
lines changed

4 files changed

+81
-31
lines changed

src/fpm.f90

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -543,6 +543,8 @@ subroutine cmd_run(settings,test)
543543
end if
544544
end if
545545

546+
547+
546548
! Check all names are valid
547549
! or no name and found more than one file
548550
toomany= size(settings%name)==0 .and. size(executables)>1
@@ -587,10 +589,10 @@ subroutine cmd_run(settings,test)
587589
if (exists(executables(i)%s)) then
588590
if(settings%runner /= ' ')then
589591
if(.not.allocated(settings%args))then
590-
call run(settings%runner//' '//executables(i)%s, &
592+
call run(settings%runner_command()//' '//executables(i)%s, &
591593
echo=settings%verbose, exitstat=stat(i))
592594
else
593-
call run(settings%runner//' '//executables(i)%s//" "//settings%args, &
595+
call run(settings%runner_command()//' '//executables(i)%s//" "//settings%args, &
594596
echo=settings%verbose, exitstat=stat(i))
595597
endif
596598
else

src/fpm_command_line.f90

Lines changed: 42 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -28,7 +28,7 @@ module fpm_command_line
2828
OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD
2929
use M_CLI2, only : set_args, lget, sget, unnamed, remaining, specified
3030
use M_CLI2, only : get_subcommand, CLI_RESPONSE_FILE
31-
use fpm_strings, only : lower, split, to_fortran_name, is_fortran_name
31+
use fpm_strings, only : lower, split, to_fortran_name, is_fortran_name, remove_characters_in_set, string_t
3232
use fpm_filesystem, only : basename, canon_path, which, run
3333
use fpm_environment, only : get_command_arguments_quoted
3434
use fpm_error, only : fpm_stop, error_t
@@ -88,9 +88,12 @@ module fpm_command_line
8888

8989
type, extends(fpm_build_settings) :: fpm_run_settings
9090
character(len=ibug),allocatable :: name(:)
91-
character(len=:),allocatable :: args
91+
character(len=:),allocatable :: args ! passed to the app
9292
character(len=:),allocatable :: runner
93+
character(len=:),allocatable :: runner_args ! passed to the runner
9394
logical :: example
95+
contains
96+
procedure :: runner_command
9497
end type
9598

9699
type, extends(fpm_run_settings) :: fpm_test_settings
@@ -141,7 +144,7 @@ module fpm_command_line
141144
& 'test', 'runner', 'install', 'update', 'list', 'help', 'version', 'publish' ]
142145

143146
character(len=:), allocatable :: val_runner, val_compiler, val_flag, val_cflag, val_cxxflag, val_ldflag, &
144-
val_profile
147+
val_profile, val_runner_args
145148

146149
! '12345678901234567890123456789012345678901234567890123456789012345678901234567890',&
147150
character(len=80), parameter :: help_text_build_common(*) = [character(len=80) :: &
@@ -268,7 +271,8 @@ subroutine get_command_line_settings(cmd_settings)
268271
run_args = &
269272
' --target " "' // &
270273
' --list F' // &
271-
' --runner " "'
274+
' --runner " "' // &
275+
' --runner-args " "'
272276

273277
compiler_args = &
274278
' --profile " "' // &
@@ -317,12 +321,17 @@ subroutine get_command_line_settings(cmd_settings)
317321
if(names(i)=='..')names(i)='*'
318322
enddo
319323

324+
! If there are additional command-line arguments, remove the additional
325+
! double quotes which have been added by M_CLI2
326+
call remove_characters_in_set(remaining,set='"')
327+
320328
c_compiler = sget('c-compiler')
321329
cxx_compiler = sget('cxx-compiler')
322330
archiver = sget('archiver')
323331
allocate(fpm_run_settings :: cmd_settings)
324332
val_runner=sget('runner')
325333
if(specified('runner') .and. val_runner=='')val_runner='echo'
334+
val_runner_args=sget('runner-args')
326335
cmd_settings=fpm_run_settings(&
327336
& args=remaining,&
328337
& profile=val_profile,&
@@ -340,6 +349,7 @@ subroutine get_command_line_settings(cmd_settings)
340349
& build_tests=.false.,&
341350
& name=names,&
342351
& runner=val_runner,&
352+
& runner_args=val_runner_args, &
343353
& verbose=lget('verbose') )
344354

345355
case('build')
@@ -565,12 +575,17 @@ subroutine get_command_line_settings(cmd_settings)
565575
if(names(i)=='..')names(i)='*'
566576
enddo
567577

578+
! If there are additional command-line arguments, remove the additional
579+
! double quotes which have been added by M_CLI2
580+
call remove_characters_in_set(remaining,set='"')
581+
568582
c_compiler = sget('c-compiler')
569583
cxx_compiler = sget('cxx-compiler')
570584
archiver = sget('archiver')
571585
allocate(fpm_test_settings :: cmd_settings)
572586
val_runner=sget('runner')
573587
if(specified('runner') .and. val_runner=='')val_runner='echo'
588+
val_runner_args=sget('runner-args')
574589
cmd_settings=fpm_test_settings(&
575590
& args=remaining, &
576591
& profile=val_profile, &
@@ -588,6 +603,7 @@ subroutine get_command_line_settings(cmd_settings)
588603
& build_tests=.true., &
589604
& name=names, &
590605
& runner=val_runner, &
606+
& runner_args=val_runner_args, &
591607
& verbose=lget('verbose') )
592608

593609
case('update')
@@ -768,7 +784,7 @@ subroutine set_help()
768784
' executables. ', &
769785
' ', &
770786
'SYNOPSIS ', &
771-
' fpm run|test --runner CMD ... -- SUFFIX_OPTIONS ', &
787+
' fpm run|test --runner CMD ... --runner-args ARGS -- SUFFIX_OPTIONS ', &
772788
' ', &
773789
'DESCRIPTION ', &
774790
' The --runner option allows specifying a program to launch ', &
@@ -784,8 +800,11 @@ subroutine set_help()
784800
' Available for both the "run" and "test" subcommands. ', &
785801
' If the keyword is specified without a value the default command ', &
786802
' is "echo". ', &
803+
' --runner-args "args" an additional option to pass command-line arguments ', &
804+
' to the runner command, instead of to the fpm app. ', &
787805
' -- SUFFIX_OPTIONS additional options to suffix the command CMD and executable ', &
788-
' file names with. ', &
806+
' file names with. These options are passed as command-line ', &
807+
' arguments to the app. ', &
789808
'EXAMPLES ', &
790809
' Use cases for ''fpm run|test --runner "CMD"'' include employing ', &
791810
' the following common GNU/Linux and Unix commands: ', &
@@ -814,6 +833,7 @@ subroutine set_help()
814833
' ', &
815834
' fpm test --runner gdb ', &
816835
' fpm run --runner "tar cvfz $HOME/bundle.tgz" ', &
836+
' fpm run --runner "mpiexec" --runner-args "-np 12" ', &
817837
' fpm run --runner ldd ', &
818838
' fpm run --runner strip ', &
819839
' fpm run --runner ''cp -t /usr/local/bin'' ', &
@@ -1430,4 +1450,20 @@ function get_fpm_env(env, default) result(val)
14301450
val = get_env(fpm_prefix//env, default)
14311451
end function get_fpm_env
14321452

1453+
1454+
!> Build a full runner command (executable + command-line arguments)
1455+
function runner_command(cmd) result(run_cmd)
1456+
class(fpm_run_settings), intent(in) :: cmd
1457+
character(len=:), allocatable :: run_cmd
1458+
!> Get executable
1459+
if (len_trim(cmd%runner)>0) then
1460+
run_cmd = trim(cmd%runner)
1461+
else
1462+
run_cmd = ''
1463+
end if
1464+
!> Append command-line arguments
1465+
if (len_trim(cmd%runner_args)>0) run_cmd = run_cmd//' '//trim(cmd%runner_args)
1466+
end function runner_command
1467+
1468+
14331469
end module fpm_command_line

src/fpm_meta.f90

Lines changed: 2 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -289,11 +289,8 @@ subroutine resolve_cmd(self,settings,error)
289289
select type (cmd=>settings)
290290
class is (fpm_run_settings) ! includes fpm_test_settings
291291

292-
if (.not.allocated(cmd%runner)) then
293-
cmd%runner = self%run_command%s
294-
else
295-
cmd%runner = self%run_command%s//' '//cmd%runner
296-
end if
292+
! Only override runner if user has not provided a custom one
293+
if (.not.len_trim(cmd%runner)>0) cmd%runner = self%run_command%s
297294

298295
end select
299296

src/fpm_strings.f90

Lines changed: 33 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -43,7 +43,7 @@ module fpm_strings
4343
public :: to_fortran_name, is_fortran_name
4444
public :: string_array_contains, string_cat, len_trim, operator(.in.), fnv_1a
4545
public :: replace, resize, str, join, glob
46-
public :: notabs, remove_newline_characters
46+
public :: notabs, remove_newline_characters, remove_characters_in_set
4747

4848
!> Module naming
4949
public :: is_valid_module_name, is_valid_module_prefix, &
@@ -1220,44 +1220,59 @@ logical function has_valid_standard_prefix(module_name,package_name) result(vali
12201220

12211221
end function has_valid_standard_prefix
12221222

1223-
! Remove all new line characters from the current string, replace them with spaces
1224-
subroutine remove_newline_characters(string)
1225-
type(string_t), intent(inout) :: string
1223+
! Remove all characters from a set from a string
1224+
subroutine remove_characters_in_set(string,set,replace_with)
1225+
character(len=:), allocatable, intent(inout) :: string
1226+
character(*), intent(in) :: set
1227+
character, optional, intent(in) :: replace_with ! Replace with this character instead of removing
12261228

12271229
integer :: feed,length
12281230

1229-
character(*), parameter :: CRLF = new_line('a')//achar(13)
1230-
character(*), parameter :: SPACE = ' '
1231+
if (.not.allocated(string)) return
1232+
if (len(set)<=0) return
12311233

1232-
if (.not.allocated(string%s)) return
1233-
1234-
1235-
length = len(string%s)
1236-
feed = scan(string%s,CRLF)
1234+
length = len(string)
1235+
feed = scan(string,set)
12371236

12381237
do while (length>0 .and. feed>0)
12391238

12401239
! Remove heading
12411240
if (length==1) then
1242-
string = string_t("")
1241+
string = ""
12431242

12441243
elseif (feed==1) then
1245-
string%s = string%s(2:length)
1244+
string = string(2:length)
12461245

12471246
! Remove trailing
12481247
elseif (feed==length) then
1249-
string%s = string%s(1:length-1)
1248+
string = string(1:length-1)
12501249

1251-
! In between: replace with space
1250+
! In between: replace with given character
1251+
elseif (present(replace_with)) then
1252+
string(feed:feed) = replace_with
1253+
! Or just remove
12521254
else
1253-
string%s(feed:feed) = SPACE
1255+
string = string(1:feed-1)//string(feed+1:length)
12541256
end if
12551257

1256-
length = len(string%s)
1257-
feed = scan(string%s,CRLF)
1258+
length = len(string)
1259+
feed = scan(string,set)
12581260

12591261
end do
12601262

1263+
end subroutine remove_characters_in_set
1264+
1265+
! Remove all new line characters from the current string, replace them with spaces
1266+
subroutine remove_newline_characters(string)
1267+
type(string_t), intent(inout) :: string
1268+
1269+
integer :: feed,length
1270+
1271+
character(*), parameter :: CRLF = new_line('a')//achar(13)
1272+
character(*), parameter :: SPACE = ' '
1273+
1274+
call remove_characters_in_set(string%s,set=CRLF,replace_with=SPACE)
1275+
12611276
end subroutine remove_newline_characters
12621277

12631278
!>AUTHOR: John S. Urban

0 commit comments

Comments
 (0)