M_CLI2 Module

NAME

M_CLI2(3fm) - [ARGUMENTS::M_CLI2::INTRO] command line argument
parsing using a prototype command
(LICENSE:PD)

SYNOPSIS

Available procedures and variables:

  ! basic procedures
  use M_CLI2, only : set_args, get_args, specified, set_mode
  ! convenience functions
  use M_CLI2, only : dget, iget, lget, rget, sget, cget
  use M_CLI2, only : dgets, igets, lgets, rgets, sgets, cgets
  ! variables
  use M_CLI2, only : unnamed, remaining, args
  ! working with non-allocatable strings and arrays
  use M_CLI2, only : get_args_fixed_length, get_args_fixed_size
  ! special function for creating subcommands
  use M_CLI2, only : get_subcommand(3f)

DESCRIPTION

The M_CLI2 module cracks a Unix-style command line.

Typically one call to SET_ARGS(3f) is made to define the command
arguments, set default values and parse the command line. Then a call
is made to the convenience procedures or GET_ARGS(3f) proper for each
command keyword to obtain the argument values.

Detailed descriptions of each procedure and example programs are
included.

EXAMPLE

Sample minimal program which may be called in various ways:

 mimimal -x 100.3 -y 3.0e4
 mimimal --xvalue=300 --debug
 mimimal --yvalue 400
 mimimal -x 10 file1 file2 file3

Program example:

 program minimal
 use M_CLI2,  only : set_args, lget, rget, sgets
 implicit none
 real    :: x, y
 integer :: i
 character(len=:),allocatable :: filenames(:)
    ! define and crack command line
    call set_args(' --yvalue:y 0.0 --xvalue:x 0.0 --debug F')
    ! get values
    x=rget('xvalue')
    y=rget('yvalue')
    if(lget('debug'))then
       write(*,*)'X=',x
       write(*,*)'Y=',y
       write(*,*)'ATAN2(Y,X)=',atan2(x=x,y=y)
    else
       write(*,*)atan2(x=x,y=y)
    endif
    filenames=sgets() ! sget with no name gets "unnamed" values
    if(size(filenames) > 0)then
       write(*,'(g0)')'filenames:'
       write(*,'(i6.6,3a)')(i,'[',filenames(i),']',i=1,size(filenames))
    endif
 end program minimal

Sample program using get_args() and variants

 program demo_M_CLI2
 use M_CLI2,  only : set_args, get_args
 use M_CLI2,  only : filenames=>unnamed
 use M_CLI2,  only : get_args_fixed_length, get_args_fixed_size
 implicit none
 integer                      :: i
 integer,parameter            :: dp=kind(0.0d0)
  !
  ! Define ARGS
 real                         :: x, y, z
 logical                      :: l, lbig
 character(len=40)            :: label    ! FIXED LENGTH
 real(kind=dp),allocatable    :: point(:)
 logical,allocatable          :: logicals(:)
 character(len=:),allocatable :: title    ! VARIABLE LENGTH
 real                         :: p(3)     ! FIXED SIZE
 logical                      :: logi(3)  ! FIXED SIZE
  !
  ! DEFINE AND PARSE (TO SET INITIAL VALUES) COMMAND LINE
  !   o set a value for all keywords.
  !   o double-quote strings, strings must be at least one space
  !     because adjacent double-quotes designate a double-quote
  !     in the value.
  !   o set all logical values to F
  !   o numeric values support an "e" or "E" exponent
  !   o for lists delimit with a comma, colon, or space
 call set_args('                         &
         & -x 1 -y 2 -z 3                &
         & -p -1 -2 -3                   &
         & --point 11.11, 22.22, 33.33e0 &
         & --title "my title" -l F -L F  &
         & --logicals  F F F F F         &
         & --logi F T F                  &
         & --label " " &
         ! note space between quotes is required
         & ')
  ! Assign values to elements using G_ARGS(3f).
  ! non-allocatable scalars can be done up to twenty per call
 call get_args('x',x, 'y',y, 'z',z, 'l',l, 'L',lbig)
  ! As a convenience multiple pairs of keywords and variables may be
  ! specified if and only if all the values are scalars and the CHARACTER
  ! variables are fixed-length or pre-allocated.
  !
  ! After SET_ARGS(3f) has parsed the command line
  ! GET_ARGS(3f) retrieves the value of keywords accept for
  ! two special cases. For fixed-length CHARACTER variables
  ! see GET_ARGS_FIXED_LENGTH(3f). For fixed-size arrays see
  ! GET_ARGS_FIXED_SIZE(3f).
  !
  ! allocatables should be done one at a time
 call get_args('title',title) ! allocatable string
 call get_args('point',point) ! allocatable arrays
 call get_args('logicals',logicals)
  !
  ! less commonly ...

  ! for fixed-length strings
 call get_args_fixed_length('label',label)

  ! for non-allocatable arrays
 call get_args_fixed_size('p',p)
 call get_args_fixed_size('logi',logi)
  !
  ! all done parsing, use values
 write(*,*)'x=',x, 'y=',y, 'z=',z, x+y+z
 write(*,*)'p=',p
 write(*,*)'point=',point
 write(*,*)'title=',title
 write(*,*)'label=',label
 write(*,*)'l=',l
 write(*,*)'L=',lbig
 write(*,*)'logicals=',logicals
 write(*,*)'logi=',logi
  !
  ! unnamed strings
  !
 if(size(filenames) > 0)then
    write(*,'(i6.6,3a)')(i,'[',filenames(i),']',i=1,size(filenames))
 endif
  !
 end program demo_M_CLI2

AUTHOR

 John S. Urban, 2019

LICENSE

 Public Domain

SEE ALSO

 + get_args(3f)
 + get_args_fixed_size(3f)
 + get_args_fixed_length(3f)
 + get_subcommand(3f)
 + set_mode(3f)
 + specified(3f)

Note that the convenience routines are described under get_args(3f): dget(3f), iget(3f), lget(3f), rget(3f), sget(3f), cget(3f) dgets(3f), igets(3f), lgets(3f), rgets(3f), sgets(3f), cgets(3f)



Contents


Variables

Type Visibility Attributes Name Initial
logical, public, save :: CLI_RESPONSE_FILE = .false.
character(len=:), public, allocatable :: args(:)
character(len=:), public, allocatable :: remaining
character(len=:), public, allocatable :: unnamed(:)

Interfaces

public interface cgets

  • private function cgs(n)

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: n

    Return Value complex, allocatable, (:)

  • private function cg()

    Arguments

    None

    Return Value complex, allocatable, (:)

public interface dgets

  • private function dgs(n)

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: n

    Return Value real(kind=dp), allocatable, (:)

  • private function dg()

    Arguments

    None

    Return Value real(kind=dp), allocatable, (:)

public interface get_args

  • private subroutine get_anyarray_d(keyword, darray, delimiters)

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: keyword
    real(kind=dp), intent(out), allocatable :: darray(:)
    character(len=*), intent(in), optional :: delimiters

public interface get_args_fixed_length

  • private subroutine get_args_fixed_length_a_array(keyword, strings, delimiters)

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: keyword
    character(len=*), allocatable :: strings(:)
    character(len=*), intent(in), optional :: delimiters

public interface get_args_fixed_size

  • private subroutine get_fixedarray_class(keyword, generic, delimiters)

    NAME

    get_args(3f) - [ARGUMENTS:M_CLI2] return keyword values when parsing
    command line arguments
    (LICENSE:PD)
    

    SYNOPSIS

    get_args(3f) and its convenience functions:

     use M_CLI2, only : get_args
     ! convenience functions
     use M_CLI2, only : dget, iget, lget, rget, sget, cget
     use M_CLI2, only : dgets, igets, lgets, rgets, sgets, cgets
    
     subroutine get_args(name,value,delimiters)
    
      character(len=*),intent(in) :: name
    
      type(${TYPE}),allocatable,intent(out) :: value(:)
      ! or
      type(${TYPE}),allocatable,intent(out) :: value
    
      character(len=*),intent(in),optional :: delimiters
    
      where ${TYPE} may be from the set
              {real,doubleprecision,integer,logical,complex,character(len=:)}
    

    DESCRIPTION

    GET_ARGS(3f) returns the value of keywords after SET_ARGS(3f) has
    been called to parse the command line. For fixed-length CHARACTER
    variables see GET_ARGS_FIXED_LENGTH(3f). For fixed-size arrays see
    GET_ARGS_FIXED_SIZE(3f).
    
    As a convenience multiple pairs of keywords and variables may be
    specified if and only if all the values are scalars and the CHARACTER
    variables are fixed-length or pre-allocated.
    

    OPTIONS

     NAME        name of commandline argument to obtain the value of
     VALUE       variable to hold returned value. The kind of the value
                 is used to determine the type of returned value. May
                 be a scalar or allocatable array. If type is CHARACTER
                 the scalar must have an allocatable length.
     DELIMITERS  By default the delimiter for array values are comma,
                 colon, and whitespace. A string containing an alternate
                 list of delimiter characters may be supplied.
    

    CONVENIENCE FUNCTIONS

    There are convenience functions that are replacements for calls to
    get_args(3f) for each supported default intrinsic type
    
      o scalars -- dget(3f), iget(3f), lget(3f), rget(3f), sget(3f),
                   cget(3f)
      o vectors -- dgets(3f), igets(3f), lgets(3f), rgets(3f),
                   sgets(3f), cgets(3f)
    
    D is for DOUBLEPRECISION, I for INTEGER, L for LOGICAL, R for REAL,
    S for string (CHARACTER), and C for COMPLEX.
    
    If the functions are called with no argument they will return the
    UNNAMED array converted to the specified type.
    

    EXAMPLE

    Sample program:

     program demo_get_args
     use M_CLI2,  only : filenames=>unnamed, set_args, get_args
     implicit none
     integer                      :: i
      ! Define ARGS
     real                         :: x, y, z
     real,allocatable             :: p(:)
     character(len=:),allocatable :: title
     logical                      :: l, lbig
      ! Define and parse (to set initial values) command line
      !   o only quote strings and use double-quotes
      !   o set all logical values to F or T.
     call set_args('         &
        & -x 1 -y 2 -z 3     &
        & -p -1,-2,-3        &
        & --title "my title" &
        & -l F -L F          &
        & --label " "        &
        & ')
      ! Assign values to elements
      ! Scalars
     call get_args('x',x,'y',y,'z',z,'l',l,'L',lbig)
      ! Allocatable string
     call get_args('title',title)
      ! Allocatable arrays
     call get_args('p',p)
      ! Use values
     write(*,'(1x,g0,"=",g0)')'x',x, 'y',y, 'z',z
     write(*,*)'p=',p
     write(*,*)'title=',title
     write(*,*)'l=',l
     write(*,*)'L=',lbig
     if(size(filenames) > 0)then
        write(*,'(i6.6,3a)')(i,'[',filenames(i),']',i=1,size(filenames))
     endif
     end program demo_get_args
    

    AUTHOR

      John S. Urban, 2019
    

    LICENSE

      Public Domain
    

    NAME

    get_args_fixed_length(3f) - [ARGUMENTS:M_CLI2] return keyword values
    for fixed-length string when parsing command line
    (LICENSE:PD)
    

    SYNOPSIS

    subroutine get_args_fixed_length(name,value)
    
     character(len=*),intent(in)  :: name
     character(len=:),allocatable :: value
     character(len=*),intent(in),optional :: delimiters
    

    DESCRIPTION

    get_args_fixed_length(3f) returns the value of a string
    keyword when the string value is a fixed-length CHARACTER
    variable.
    

    OPTIONS

    NAME   name of commandline argument to obtain the value of
    
    VALUE  variable to hold returned value.
           Must be a fixed-length CHARACTER variable.
    
    DELIMITERS  By default the delimiter for array values are comma,
                colon, and whitespace. A string containing an alternate
                list of delimiter characters may be supplied.
    

    EXAMPLE

    Sample program:

     program demo_get_args_fixed_length
     use M_CLI2,  only : set_args, get_args_fixed_length
     implicit none
    
      ! Define args
     character(len=80)   :: title
      ! Parse command line
     call set_args(' --title "my title" ')
      ! Assign values to variables
     call get_args_fixed_length('title',title)
      ! Use values
     write(*,*)'title=',title
    
     end program demo_get_args_fixed_length
    

    AUTHOR

      John S. Urban, 2019
    

    LICENSE

      Public Domain
    

    NAME

    get_args_fixed_size(3f) - [ARGUMENTS:M_CLI2] return keyword values
    for fixed-size array when parsing command line arguments
    (LICENSE:PD)
    

    SYNOPSIS

    subroutine get_args_fixed_size(name,value)
    
     character(len=*),intent(in) :: name
     [real|doubleprecision|integer|logical|complex] :: value(NNN)
        or
     character(len=MMM) :: value(NNN)
    
     character(len=*),intent(in),optional :: delimiters
    

    DESCRIPTION

    get_args_fixed_size(3f) returns the value of keywords for fixed-size
    arrays after set_args(3f) has been called.  On input on the command
    line all values of the array must be specified.
    

    OPTIONS

    NAME        name of commandline argument to obtain the value of
    
    VALUE       variable to hold returned values. The kind of the value
                is used to determine the type of returned value. Must be
                a fixed-size array. If type is CHARACTER the length must
                also be fixed.
    
    DELIMITERS  By default the delimiter for array values are comma,
                colon, and whitespace. A string containing an alternate
                list of delimiter characters may be supplied.
    

    EXAMPLE

    Sample program:

     program demo_get_args_fixed_size
     use M_CLI2,  only : set_args, get_args_fixed_size
     implicit none
     integer,parameter   :: dp=kind(0.0d0)
     ! DEFINE ARGS
     real                :: x(2)
     real(kind=dp)       :: y(2)
     integer             :: p(3)
     character(len=80)   :: title(1)
     logical             :: l(4), lbig(4)
     complex             :: cmp(2)
     ! DEFINE AND PARSE (TO SET INITIAL VALUES) COMMAND LINE
     !   o only quote strings
     !   o set all logical values to F or T.
     call set_args(' &
        & -x 10.0,20.0 &
        & -y 11.0,22.0 &
        & -p -1,-2,-3 &
        & --title "my title" &
        & -l F,T,F,T -L T,F,T,F  &
        & --cmp 111,222.0,333.0e0,4444 &
        & ')
     ! ASSIGN VALUES TO ELEMENTS
        call get_args_fixed_size('x',x)
        call get_args_fixed_size('y',y)
        call get_args_fixed_size('p',p)
        call get_args_fixed_size('title',title)
        call get_args_fixed_size('l',l)
        call get_args_fixed_size('L',lbig)
        call get_args_fixed_size('cmp',cmp)
     ! USE VALUES
        write(*,*)'x=',x
        write(*,*)'p=',p
        write(*,*)'title=',title
        write(*,*)'l=',l
        write(*,*)'L=',lbig
        write(*,*)'cmp=',cmp
     end program demo_get_args_fixed_size
    

    Results:

    AUTHOR

      John S. Urban, 2019
    

    LICENSE

      Public Domain
    

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: keyword
    class(*) :: generic(:)
    character(len=*), intent(in), optional :: delimiters

public interface igets

  • private function igs(n)

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: n

    Return Value integer, allocatable, (:)

  • private function ig()

    Arguments

    None

    Return Value integer, allocatable, (:)

public interface lgets

  • private function lgs(n)

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: n

    Return Value logical, allocatable, (:)

  • private function lg()

    Arguments

    None

    Return Value logical, allocatable, (:)

public interface rgets

  • private function rgs(n)

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: n

    Return Value real, allocatable, (:)

  • private function rg()

    Arguments

    None

    Return Value real, allocatable, (:)

public interface sgets

  • private function sgs(n, delims)

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: n
    character(len=*), intent(in), optional :: delims

    Return Value character(len=:), allocatable, (:)

  • private function sg()

    Arguments

    None

    Return Value character(len=:), allocatable, (:)


Functions

public function cget(n)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: n

Return Value complex

public function dget(n)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: n

Return Value real(kind=dp)

public function get_subcommand() result(sub)

Sample program:

Read more…

Arguments

None

Return Value character(len=:), allocatable

public function iget(n)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: n

Return Value integer

public function lget(n)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: n

Return Value logical

public function rget(n)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: n

Return Value real

public function sget(n)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: n

Return Value character(len=:), allocatable

public impure elemental function specified(key)

Sample program:

Read more…

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: key

Return Value logical


Subroutines

public subroutine print_dictionary(header, stop)

Typical usage:

Read more…

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in), optional :: header
logical, intent(in), optional :: stop

public subroutine set_args(prototype, help_text, version_text, string, prefix, ierr, errmsg)

Sample program:

Read more…

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: prototype
character(len=*), intent(in), optional :: help_text(:)
character(len=*), intent(in), optional :: version_text(:)
character(len=*), intent(in), optional :: string
character(len=*), intent(in), optional :: prefix
integer, intent(out), optional :: ierr
character(len=:), intent(out), optional, allocatable :: errmsg

public impure elemental subroutine set_mode(key, mode)

Sample program:

Read more…

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: key
logical, intent(in), optional :: mode