Skip to content

Commit 2fcfd71

Browse files
committed
add help text for --runner parameter
1 parent 7908a5c commit 2fcfd71

File tree

1 file changed

+86
-31
lines changed

1 file changed

+86
-31
lines changed

fpm/src/fpm_command_line.f90

Lines changed: 86 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -54,9 +54,12 @@ module fpm_command_line
5454

5555
character(len=:), allocatable :: version_text(:)
5656
character(len=:), allocatable :: help_new(:), help_fpm(:), help_run(:), &
57-
& help_test(:), help_build(:), help_usage(:), &
57+
& help_test(:), help_build(:), help_usage(:), help_runner(:), &
5858
& help_text(:), help_install(:), help_help(:), &
5959
& help_list(:), help_list_dash(:), help_list_nodash(:)
60+
character(len=20),parameter :: manual(*)=[ character(len=20) ::&
61+
& 'fpm','new','build','run','test',&
62+
& 'runner','list','help','version']
6063

6164
character(len=:), allocatable :: charbug
6265
contains
@@ -163,43 +166,44 @@ subroutine get_command_line_settings(cmd_settings)
163166
& backfill=lget('backfill') )
164167
endif
165168

166-
case('help')
169+
case('help','manual')
167170
call set_args(' ',help_help,version_text)
168171
if(size(unnamed).lt.2)then
169-
unnamed=['help', 'fpm ']
172+
if(unnamed(1).eq.'help')then
173+
unnamed=[' ', 'fpm']
174+
else
175+
unnamed=manual
176+
endif
177+
elseif(unnamed(2).eq.'manual')then
178+
unnamed=manual
170179
endif
171180
widest=256
172181
allocate(character(len=widest) :: help_text(0))
173182
do i=2,size(unnamed)
174183
select case(unnamed(i))
184+
case(' ' )
185+
case('fpm ' )
186+
help_text=[character(len=widest) :: help_text, help_fpm]
187+
case('new ' )
188+
help_text=[character(len=widest) :: help_text, help_new]
175189
case('build ' )
176190
help_text=[character(len=widest) :: help_text, help_build]
177191
case('run ' )
178192
help_text=[character(len=widest) :: help_text, help_run]
179-
case('help ' )
180-
help_text=[character(len=widest) :: help_text, help_help]
181193
case('test ' )
182194
help_text=[character(len=widest) :: help_text, help_test]
183-
case('new ' )
184-
help_text=[character(len=widest) :: help_text, help_new]
185-
case('fpm ' )
186-
help_text=[character(len=widest) :: help_text, help_fpm]
195+
case('runner' )
196+
help_text=[character(len=widest) :: help_text, help_runner]
187197
case('list ' )
188198
help_text=[character(len=widest) :: help_text, help_list]
189-
case('version' )
190-
help_text=[character(len=widest) :: help_text, version_text]
191-
case('manual ' )
192-
help_text=[character(len=widest) :: help_text, help_fpm]
193-
help_text=[character(len=widest) :: help_text, help_new]
194-
help_text=[character(len=widest) :: help_text, help_build]
195-
help_text=[character(len=widest) :: help_text, help_run]
196-
help_text=[character(len=widest) :: help_text, help_test]
199+
case('help ' )
197200
help_text=[character(len=widest) :: help_text, help_help]
198-
help_text=[character(len=widest) :: help_text, help_list]
201+
case('version' )
199202
help_text=[character(len=widest) :: help_text, version_text]
200203
case default
201204
help_text=[character(len=widest) :: help_text, &
202-
& 'ERROR: unknown help topic "'//trim(unnamed(i))//'"']
205+
& '<ERROR> unknown help topic "'//trim(unnamed(i))//'"']
206+
!!& '<ERROR> unknown help topic "'//trim(unnamed(i)).'not found in:',manual]
203207
end select
204208
enddo
205209
call printhelp(help_text)
@@ -224,7 +228,7 @@ subroutine get_command_line_settings(cmd_settings)
224228
endif
225229

226230
allocate(fpm_test_settings :: cmd_settings)
227-
charbug=sget('runner')
231+
charbug=sget('runner')
228232
cmd_settings=fpm_test_settings( name=names, list=lget('list'), &
229233
& release=lget('release'), args=remaining ,runner=charbug )
230234

@@ -303,6 +307,64 @@ subroutine set_help()
303307
' test [NAME(s)] [--release] [--runner "CMD"] [--list] [-- ARGS] ', &
304308
' ']
305309
help_usage=[character(len=80) :: &
310+
'' ]
311+
help_runner=[character(len=80) :: &
312+
'NAME ', &
313+
' --runner(1) - a shared option for specifying an application to launch ', &
314+
' executables. ', &
315+
' ', &
316+
'SYNOPSIS ', &
317+
' fpm run|test --runner CMD ... ', &
318+
' ', &
319+
'DESCRIPTION ', &
320+
' The --runner option allows specifying a program to launch ', &
321+
' executables selected via the fpm(1) subcommands "run" and "test". This ', &
322+
' gives easy recourse to utilities such as debuggers and other tools ', &
323+
' that wrap other executables. ', &
324+
' ', &
325+
' These external commands are not part of fpm(1) itself as they vary ', &
326+
' from platform to platform or require independent installation. ', &
327+
' ', &
328+
'OPTION ', &
329+
' --runner ''CMD'' quoted command used to launch the fpm(1) executables. ', &
330+
' Available for both the "run" and "test" subcommands. ', &
331+
' ', &
332+
'EXAMPLES ', &
333+
' Use cases for ''fpm run|test --runner "CMD"'' include employing ', &
334+
' the following common GNU/Linux and Unix commands: ', &
335+
' ', &
336+
' INTERROGATE ', &
337+
' + nm - list symbols from object files ', &
338+
' + size - list section sizes and total size. ', &
339+
' + ldd - print shared object dependencies ', &
340+
' + ls - list directory contents ', &
341+
' + stat - display file or file system status ', &
342+
' + file - determine file type ', &
343+
' PERFORMANCE AND DEBUGGING ', &
344+
' + gdb - The GNU Debugger ', &
345+
' + valgrind - a suite of tools for debugging and profiling ', &
346+
' + time - time a simple command or give resource usage ', &
347+
' + timeout - run a command with a time limit ', &
348+
' COPY ', &
349+
' + install - copy files and set attributes ', &
350+
' + tar - an archiving utility ', &
351+
' ALTER ', &
352+
' + rm - remove files or directories ', &
353+
' + chmod - change permissions of a file ', &
354+
' + strip - remove unnecessary information from strippable files ', &
355+
' ', &
356+
' For example ', &
357+
' ', &
358+
' fpm test --runner gdb ', &
359+
' fpm run --runner "tar cvfz $HOME/bundle.tgz" ', &
360+
' fpm run --runner ldd ', &
361+
' fpm run --runner strip ', &
362+
' fpm run --runner ''cp -t /usr/local/bin'' ', &
363+
' ', &
364+
' # bash(1) alias example: ', &
365+
' alias fpm-install="ffpm run --release --runner \ ', &
366+
' ''install -vbp -m 0711 -t ~/.local/bin''" ', &
367+
' fpm-install ', &
306368
'' ]
307369
help_fpm=[character(len=80) :: &
308370
'NAME ', &
@@ -417,11 +479,7 @@ subroutine set_help()
417479
' build. ', &
418480
' --list list candidates instead of building or running them ', &
419481
' --runner CMD A command to prefix the program execution paths with. ', &
420-
' For use with utilities like valgrind(1), time(1), and ', &
421-
' other utilities that launch executables; commands that ', &
422-
' inspect the files like ldd(1), file(1), and ls(1); and ', &
423-
' ones that copy or change files like strip(1) and ', &
424-
' install(1). ', &
482+
' see "fpm help runner" for further details. ', &
425483
' -- ARGS optional arguments to pass to the program(s). ', &
426484
' The same arguments are passed to all names ', &
427485
' specified. ', &
@@ -439,7 +497,7 @@ subroutine set_help()
439497
' fpm run prg1 prg2 --release ', &
440498
' ', &
441499
' # install executables in directory (assuming install(1) exists) ', &
442-
' fpm run -c ''install -b -m 0711 -p -t /usr/local/bin'' ', &
500+
' fpm run --runner ''install -b -m 0711 -p -t /usr/local/bin'' ', &
443501
' ', &
444502
'SEE ALSO ', &
445503
' The fpm(1) home page at https://github.com/fortran-lang/fpm ', &
@@ -492,6 +550,7 @@ subroutine set_help()
492550
' ', &
493551
'SYNOPSIS ', &
494552
' fpm help [fpm] [new] [build] [run] [test] [help] [version] [manual] ', &
553+
' [runner] ', &
495554
' ', &
496555
'DESCRIPTION ', &
497556
' The "fpm help" command is an alternative to the --help parameter ', &
@@ -617,11 +676,7 @@ subroutine set_help()
617676
' build. ', &
618677
' --list list candidates instead of building or running them ', &
619678
' --runner CMD A command to prefix the program execution paths with. ', &
620-
' For use with utilities like valgrind(1), time(1), and ', &
621-
' other utilities that launch executables; commands that ', &
622-
' inspect the files like ldd(1), file(1), and ls(1); and ', &
623-
' ones that copy or change files like strip(1) and ', &
624-
' install(1). ', &
679+
' see "fpm help runner" for further details. ', &
625680
' -- ARGS optional arguments to pass to the test program(s). ', &
626681
' The same arguments are passed to all test names ', &
627682
' specified. ', &

0 commit comments

Comments
 (0)