Skip to content

Commit bd1a54d

Browse files
authored
Add developer documentation for run(3f) and example program (#933)
2 parents 92254f7 + 98eb021 commit bd1a54d

File tree

2 files changed

+77
-24
lines changed

2 files changed

+77
-24
lines changed

src/fpm_filesystem.F90

Lines changed: 69 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -774,31 +774,32 @@ subroutine filewrite(filename,filedata)
774774

775775
end subroutine filewrite
776776

777-
function which(command) result(pathname)
777+
!>AUTHOR: John S. Urban
778+
!!LICENSE: Public Domain
778779
!>
779-
!!##NAME
780+
!!##Name
780781
!! which(3f) - [M_io:ENVIRONMENT] given a command name find the pathname by searching
781782
!! the directories in the environment variable $PATH
782783
!! (LICENSE:PD)
783784
!!
784-
!!##SYNTAX
785+
!!##Syntax
785786
!! function which(command) result(pathname)
786787
!!
787788
!! character(len=*),intent(in) :: command
788789
!! character(len=:),allocatable :: pathname
789790
!!
790-
!!##DESCRIPTION
791+
!!##Description
791792
!! Given a command name find the first file with that name in the directories
792793
!! specified by the environment variable $PATH.
793794
!!
794-
!!##OPTIONS
795+
!!##options
795796
!! COMMAND the command to search for
796797
!!
797-
!!##RETURNS
798+
!!##Returns
798799
!! PATHNAME the first pathname found in the current user path. Returns blank
799800
!! if the command is not found.
800801
!!
801-
!!##EXAMPLE
802+
!!##Example
802803
!!
803804
!! Sample program:
804805
!!
@@ -812,11 +813,7 @@ function which(command) result(pathname)
812813
!! write(*,*)'install is ',which('install')
813814
!! end program demo_which
814815
!!
815-
!!##AUTHOR
816-
!! John S. Urban
817-
!!##LICENSE
818-
!! Public Domain
819-
816+
function which(command) result(pathname)
820817
character(len=*),intent(in) :: command
821818
character(len=:),allocatable :: pathname, checkon, paths(:), exts(:)
822819
integer :: i, j
@@ -854,8 +851,66 @@ function which(command) result(pathname)
854851
enddo SEARCH
855852
end function which
856853

857-
!> echo command string and pass it to the system for execution
858-
!call run(cmd,echo=.false.,exitstat=exitstat,verbose=.false.,redirect='')
854+
!>AUTHOR: fpm(1) contributors
855+
!!LICENSE: MIT
856+
!>
857+
!!##Name
858+
!! run(3f) - execute specified system command and selectively echo
859+
!! command and output to a file and/or stdout.
860+
!! (LICENSE:MIT)
861+
!!
862+
!!##Syntax
863+
!! subroutine run(cmd,echo,exitstat,verbose,redirect)
864+
!!
865+
!! character(len=*), intent(in) :: cmd
866+
!! logical,intent(in),optional :: echo
867+
!! integer, intent(out),optional :: exitstat
868+
!! logical, intent(in), optional :: verbose
869+
!! character(*), intent(in), optional :: redirect
870+
!!
871+
!!##Description
872+
!! Execute the specified system command. Optionally
873+
!!
874+
!! + echo the command before execution
875+
!! + return the system exit status of the command.
876+
!! + redirect the output of the command to a file.
877+
!! + echo command output to stdout
878+
!!
879+
!! Calling run(3f) is preferred to direct calls to
880+
!! execute_command_line(3f) in the fpm(1) source to provide a standard
881+
!! interface where output modes can be specified.
882+
!!
883+
!!##Options
884+
!! CMD System command to execute
885+
!! ECHO Whether to echo the command being executed or not
886+
!! Defaults to .TRUE. .
887+
!! VERBOSE Whether to redirect the command output to a null device or not
888+
!! Defaults to .TRUE. .
889+
!! REDIRECT Filename to redirect stdout and stderr of the command into.
890+
!! If generated it is closed before run(3f) returns.
891+
!! EXITSTAT The system exit status of the command when supported by
892+
!! the system. If not present and a non-zero status is
893+
!! generated program termination occurs.
894+
!!
895+
!!##Example
896+
!!
897+
!! Sample program:
898+
!!
899+
!! Checking the error message and counting lines:
900+
!!
901+
!! program demo_run
902+
!! use fpm_filesystem, only : run
903+
!! implicit none
904+
!! logical,parameter :: T=.true., F=.false.
905+
!! integer :: exitstat
906+
!! character(len=:),allocatable :: cmd
907+
!! cmd='ls -ltrasd *.md'
908+
!! call run(cmd)
909+
!! call run(cmd,exitstat=exitstat)
910+
!! call run(cmd,echo=F)
911+
!! call run(cmd,verbose=F)
912+
!! end program demo_run
913+
!!
859914
subroutine run(cmd,echo,exitstat,verbose,redirect)
860915
character(len=*), intent(in) :: cmd
861916
logical,intent(in),optional :: echo

src/fpm_strings.f90

Lines changed: 8 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -236,9 +236,9 @@ pure function fnv_1a_string_t(input, seed) result(hash)
236236
end function fnv_1a_string_t
237237

238238

239-
!>Author: John S. Urban
240-
!!License: Public Domain
241-
!! Changes a string to lowercase over optional specified column range
239+
!>Author: John S. Urban
240+
!!License: Public Domain
241+
!! Changes a string to lowercase over optional specified column range
242242
elemental pure function lower(str,begin,end) result (string)
243243

244244
character(*), intent(In) :: str
@@ -624,8 +624,9 @@ pure function join(str,sep,trm,left,right,start,end) result (string)
624624
if(present(end))string=string//end
625625
end function join
626626

627-
!>##AUTHOR John S. Urban
628-
!!##LICENSE Public Domain
627+
!>AUTHOR: John S. Urban
628+
!!LICENSE: Public Domain
629+
!>
629630
!!## NAME
630631
!! glob(3f) - [fpm_strings:COMPARE] compare given string for match to
631632
!! pattern which may contain wildcard characters
@@ -1259,6 +1260,8 @@ subroutine remove_newline_characters(string)
12591260

12601261
end subroutine remove_newline_characters
12611262

1263+
!>AUTHOR: John S. Urban
1264+
!!LICENSE: Public Domain
12621265
!>
12631266
!!### NAME
12641267
!! notabs(3f) - [fpm_strings:NONALPHA] expand tab characters
@@ -1316,11 +1319,6 @@ end subroutine remove_newline_characters
13161319
!!### SEE ALSO
13171320
!! GNU/Unix commands expand(1) and unexpand(1)
13181321
!!
1319-
!!### AUTHOR
1320-
!! John S. Urban
1321-
!!
1322-
!!### LICENSE
1323-
!! Public Domain
13241322
elemental impure subroutine notabs(instr,outstr,ilen)
13251323

13261324
! ident_31="@(#)fpm_strings::notabs(3f): convert tabs to spaces while maintaining columns, remove CRLF chars"

0 commit comments

Comments
 (0)