LCOV - code coverage report
Current view: top level - src - mo_cli.f90 (source / functions) Hit Total Coverage
Test: forces coverage Lines: 139 253 54.9 %
Date: 2024-03-13 19:03:28 Functions: 10 21 47.6 %

          Line data    Source code
       1             : !> \file    mo_cli.f90
       2             : !> \brief \copybrief mo_cli
       3             : !> \details \copydetails mo_cli
       4             : 
       5             : !> \brief   Module to parse command line arguments.
       6             : !> \version 0.1
       7             : !> \authors Sebastian Mueller
       8             : !> \date    May 2021
       9             : !> \details A simple parser for command line arguments.
      10             : !!          You can define options and then parse the given command.
      11             : !!          Option can be with or without passed values and they can be set
      12             : !!          as required.
      13             : !!
      14             : !!          The following example demonstrates the functionality:
      15             : !!          \code{.f90}
      16             : !!          program main
      17             : !!            use mo_cli, only: cli_parser
      18             : !!            implicit none
      19             : !!            type(cli_parser) :: parser
      20             : !!
      21             : !!            parser = cli_parser( &
      22             : !!              description="This program has a CLI.", &
      23             : !!              add_version_option=.true., version="1.3")
      24             : !!            call parser%add_option( &
      25             : !!              "cwd", &
      26             : !!              blank=.true., &
      27             : !!              required=.true., &
      28             : !!              help="The working directory.")
      29             : !!            call parser%add_option( &
      30             : !!              name="file", &
      31             : !!              s_name="f", &
      32             : !!              has_value=.true., &
      33             : !!              value_name="path", &
      34             : !!              default="none", &
      35             : !!              help="Your file path.")
      36             : !!            call parser%add_option("opt", help="A switch")
      37             : !!
      38             : !!            call parser%parse()
      39             : !!
      40             : !!            print*, "file: ", parser%option_value("file")
      41             : !!            print*, "dir: ", parser%option_value("cwd")
      42             : !!            print*, "opt: ", parser%option_was_read("opt")
      43             : !!
      44             : !!          end program main
      45             : !!          \endcode
      46             : !!          You can call the program with:
      47             : !!          \code{.sh}
      48             : !!          $ ./prog --opt -f file.txt /dir/
      49             : !!           file: file.txt
      50             : !!           dir: /dir/
      51             : !!           opt:  T
      52             : !!          \endcode
      53             : !!          As you see, you can automatically create help and version options:
      54             : !!          \code{.sh}
      55             : !!          $ ./prog -h
      56             : !!          $ ./prog -V
      57             : !!          \endcode
      58             : !> \copyright Copyright 2005-\today, the CHS Developers, Sabine Attinger: All rights reserved.
      59             : !! FORCES is released under the LGPLv3+ license \license_note
      60             : module mo_cli
      61             : 
      62             :   use mo_kind, only: i4
      63             :   use mo_message, only: error_message, message
      64             : 
      65             :   implicit none
      66             : 
      67             :   private
      68             : 
      69             :   !> \class   option
      70             :   !> \brief   This is a container for a single command line option.
      71             :   type, public :: option
      72             :     character(:), allocatable :: help !< description of the option
      73             :     character(:), allocatable :: name !< long name (will be double hyphenated: --opt)
      74             :     character(1) :: s_name = "" !< short name (will be hyphenated: -o)
      75             :     logical :: has_s_name = .false. !< whether the option has a short name
      76             :     logical :: required = .false. !< whether the option is required
      77             :     logical :: blank = .false. !< whether the option is passed blank without hyphenated name (only latter one possible)
      78             :     logical :: was_read = .false. !< whether the option was read from command line
      79             :     logical :: has_value = .false. !< whether the option has a value
      80             :     logical :: has_default = .false. !< whether the option has a default value
      81             :     logical :: repeated = .false. !< whether the option can be read repeatedly
      82             :     integer(i4) :: read_count = 0_i4 !< number of reads (-ooo)
      83             :     character(:), allocatable :: value !< value of the option (if has one)
      84             :     character(:), allocatable :: value_name !< name of the value for the help text (default "value")
      85             :     character(:), allocatable :: default !< default value of the option (if has one)
      86             :   contains
      87             :     !> \copydoc mo_cli::print_info
      88             :     procedure :: print_info !< \see mo_cli::print_info
      89             :     !> \copydoc mo_cli::is_given_arg
      90             :     procedure :: is_given_arg !< \see mo_cli::is_given_arg
      91             :   end type option
      92             : 
      93             :   interface option
      94             :     procedure new_option
      95             :   end interface option
      96             : 
      97             :   !> \class   cli_parser
      98             :   !> \brief   This is a parser for command line arguments.
      99             :   !> \details \copydetails mo_cli
     100             :   type, public :: cli_parser
     101             :     character(:), allocatable :: prog !< Program name (default will be arg(0)).
     102             :     character(:), allocatable :: description !< help text for the cli
     103             :     character(:), allocatable :: version !< Program version
     104             :     logical :: has_help = .true. !< whether the parser cares about the help text (--help / -h)
     105             :     logical :: has_version = .false. !< whether the parser cares about the version text (--version / -V)
     106             :     logical :: has_blank_option = .false. !< whether the parser has a blank option.
     107             :     logical :: has_logger = .false. !< whether the parser should setup the logger.
     108             :     type(option), dimension(:), allocatable :: options !< defined options
     109             :   contains
     110             :     !> \copydoc mo_cli::add_option
     111             :     procedure :: add_option !< \see mo_cli::add_option
     112             :     !> \copydoc mo_cli::get_option
     113             :     procedure :: get_option !< \see mo_cli::get_option
     114             :     !> \copydoc mo_cli::get_option_index
     115             :     procedure :: get_option_index !< \see mo_cli::get_option_index
     116             :     !> \copydoc mo_cli::cnt_options
     117             :     procedure :: cnt_options !< \see mo_cli::cnt_options
     118             :     !> \copydoc mo_cli::option_was_read
     119             :     procedure :: option_was_read !< \see mo_cli::option_was_read
     120             :     !> \copydoc mo_cli::option_read_count
     121             :     procedure :: option_read_count !< \see mo_cli::option_read_count
     122             :     !> \copydoc mo_cli::has_option
     123             :     procedure :: has_option !< \see mo_cli::has_option
     124             :     !> \copydoc mo_cli::get_blank_option_index
     125             :     procedure :: get_blank_option_index !< \see mo_cli::get_blank_option_index
     126             :     !> \copydoc mo_cli::option_value
     127             :     procedure :: option_value !< \see mo_cli::option_value
     128             :     !> \copydoc mo_cli::print_help
     129             :     procedure :: print_help !< \see mo_cli::print_help
     130             :     !> \copydoc mo_cli::parse
     131             :     procedure :: parse !< \see mo_cli::parse
     132             :   end type cli_parser
     133             : 
     134             :   interface cli_parser
     135             :     procedure new_cli_parser
     136             :   end interface cli_parser
     137             : 
     138             : contains
     139             : 
     140             :   !> \brief Create a new \ref cli_parser.
     141             :   !> \return The new \ref cli_parser.
     142           1 :   type(cli_parser) function new_cli_parser(prog, description, add_help_option, add_version_option, version, add_logger_options)
     143             :     use mo_os, only: path_split
     144             :     implicit none
     145             :     character(*), optional, intent(in) :: prog !< Program name (default will be arg(0))
     146             :     character(*), optional, intent(in) :: description !< help text for the cli
     147             :     logical, optional, intent(in) :: add_help_option !< whether to add a help option (--help, -h)
     148             :     logical, optional, intent(in) :: add_version_option !< whether to add a version option (--version, -V)
     149             :     character(*), optional, intent(in) :: version !< Program version
     150             :     logical, optional, intent(in) :: add_logger_options !< whether to add a logger options (--verbose, --quite, ...)
     151             : 
     152             :     integer(i4) :: n
     153           1 :     character(:), allocatable :: arg, prog_
     154             : 
     155           1 :     allocate(new_cli_parser%options(0))
     156             : 
     157           1 :     if (present(prog)) then
     158           0 :       new_cli_parser%prog = prog
     159             :     else
     160           1 :       call get_command_argument(0, length=n)
     161           1 :       allocate(character(n) :: arg, prog_)
     162           1 :       call get_command_argument(0, value=arg)
     163             :       call path_split(arg, tail=prog_)
     164           1 :       new_cli_parser%prog = trim(prog_)
     165             :     end if
     166             : 
     167           1 :     new_cli_parser%description = "Command line options."
     168           1 :     if (present(description)) new_cli_parser%description = description
     169           1 :     if (present(add_help_option)) new_cli_parser%has_help = add_help_option
     170           1 :     if (present(add_version_option)) new_cli_parser%has_version = add_version_option
     171           1 :     if (present(add_logger_options)) new_cli_parser%has_logger = add_logger_options
     172             : 
     173           1 :     if (new_cli_parser%has_help) call new_cli_parser%add_option( &
     174           1 :       name="help", s_name="h", help="Print this help message.")
     175             : 
     176           1 :     if (new_cli_parser%has_version .and. (.not. present(version))) &
     177           0 :       call error_message("cli_parser: when adding the version option, you need to provide a version")
     178           1 :     if (new_cli_parser%has_version) call new_cli_parser%add_option( &
     179           1 :       name="version", s_name="V", help="Print the version of the program.")
     180           1 :     new_cli_parser%version = ""
     181           1 :     if (present(version)) new_cli_parser%version = version
     182             :     ! add logging options
     183           1 :     if (new_cli_parser%has_logger) then
     184             :       call new_cli_parser%add_option( &
     185           0 :         name="verbose", s_name="v", repeated=.true., help="Increase logging verbosity level.")
     186             :       call new_cli_parser%add_option( &
     187           0 :         name="quiet", s_name="q", repeated=.true., help="Decrease logging verbosity level.")
     188             :       call new_cli_parser%add_option( &
     189           0 :         name="log-output-hostname", help="Output hostname while logging.")
     190             :       call new_cli_parser%add_option( &
     191           0 :         name="log-force-colors", help="Forces colors for the logger.")
     192             :       call new_cli_parser%add_option( &
     193           0 :         name="log-no-colors", help="Disable colors while logging.")
     194             :       call new_cli_parser%add_option( &
     195           0 :         name="log-no-format", help="Disable formatting while logging.")
     196             :       call new_cli_parser%add_option( &
     197           0 :         name="log-output-date", help="Output date while logging.")
     198             :       call new_cli_parser%add_option( &
     199           0 :         name="log-output-time", help="Output time while logging.")
     200             :     end if
     201           1 :   end function new_cli_parser
     202             : 
     203             :   !> \brief Create a new \ref option.
     204             :   !> \return The new \ref option.
     205           6 :   type(option) function new_option(name, s_name, help, has_value, value_name, default, required, blank, repeated)
     206             :     implicit none
     207             :     character(*), intent(in) :: name !< long name (will be double hyphenated: --opt)
     208             :     character(1), optional, intent(in) :: s_name !< short name (will be hyphenated: -o)
     209             :     character(*), optional, intent(in) :: help !< description of the option
     210             :     logical, optional, intent(in) :: has_value !< whether the option has a value
     211             :     character(*), optional, intent(in) :: value_name !< name of the value for the help text (default "value")
     212             :     character(*), optional, intent(in) :: default !< default value for this option
     213             :     logical, optional, intent(in) :: required !< whether the option is required
     214             :     logical, optional, intent(in) :: blank !< whether the option is passed blank without hyphenated name (only latter one possible)
     215             :     logical, optional, intent(in) :: repeated !< whether the option can be read repeatedly
     216             : 
     217           6 :     new_option%help = "No description"
     218           6 :     if (present(help)) new_option%help = help
     219             : 
     220           6 :     if (len(name) <= 1_i4) &
     221           0 :       call error_message("option: long-name needs at least 2 characters: " // name)
     222           6 :     new_option%name = name
     223             : 
     224           6 :     new_option%has_s_name = present(s_name)
     225           6 :     if (new_option%has_s_name) new_option%s_name = s_name
     226           6 :     if (new_option%has_s_name .and. (new_option%s_name == " ")) &
     227           0 :       call error_message("option: short name needs to be non empty: " // name)
     228             : 
     229           6 :     if (present(required)) new_option%required = required
     230           6 :     if (present(blank)) new_option%blank = blank
     231           6 :     if (present(has_value)) then
     232           1 :       new_option%has_value = has_value
     233           1 :       if ((.not. new_option%has_value) .and. new_option%blank) &
     234           0 :         call error_message("option: blank option needs a value: " // name)
     235             :     else
     236           5 :       new_option%has_value = new_option%blank
     237             :     end if
     238             : 
     239           6 :     new_option%value = ""
     240           6 :     new_option%value_name = ""
     241           6 :     new_option%default = ""
     242           6 :     if (new_option%has_value) then
     243           1 :       new_option%value_name = "value"
     244           1 :       if (present(value_name)) new_option%value_name = value_name
     245           1 :       if ((.not. present(value_name)) .and. new_option%blank) new_option%value_name = name
     246           1 :       new_option%has_default = present(default)
     247           1 :       if (new_option%has_default) new_option%default = default
     248             :     end if
     249             : 
     250           6 :     if ((.not. new_option%has_value) .and. new_option%required) &
     251           0 :       call error_message("option: option without value can't be required: " // name)
     252             : 
     253           6 :     if (new_option%has_value .and. new_option%has_default .and. new_option%required) &
     254           0 :       call error_message("option: option with defined default value can't be required: " // name)
     255             : 
     256           6 :     if (present(repeated)) new_option%repeated = repeated
     257           6 :     if (new_option%repeated .and. new_option%has_value) &
     258           0 :       call error_message("option: repeatedly readable options shouldn't expect a value: " // name)
     259             : 
     260           1 :   end function new_option
     261             : 
     262             :   !> \brief Add a new \ref option to the \ref cli_parser.
     263           6 :   subroutine add_option(self, name, s_name, help, has_value, value_name, default, required, blank, repeated)
     264             :     implicit none
     265             :     class(cli_parser), intent(inout) :: self
     266             :     character(*), intent(in) :: name !< long name (will be double hyphenated: --opt)
     267             :     character(1), optional, intent(in) :: s_name !< short name (will be hyphenated: -o)
     268             :     character(*), optional, intent(in) :: help !< description of the option
     269             :     logical, optional, intent(in) :: has_value !< whether the option has a value
     270             :     character(*), optional, intent(in) :: value_name !< name of the value for the help text (default "value")
     271             :     character(*), optional, intent(in) :: default !< default value for this option
     272             :     logical, optional, intent(in) :: required !< whether the option is required
     273             :     logical, optional, intent(in) :: blank !< whether the option is passed blank without hyphenated name (only latter one possible)
     274             :     logical, optional, intent(in) :: repeated !< whether the option can be read repeatedly
     275             : 
     276         138 :     type(option), dimension(size(self%options)) :: tmp_options
     277           6 :     type(option) :: added_option
     278             :     integer(i4) :: i
     279             : 
     280          23 :     added_option = option(name, s_name, help, has_value, value_name, default, required, blank, repeated)
     281           6 :     if (added_option%blank .and. self%has_blank_option) then
     282           0 :       call error_message("cli_parser%add_option: only one blank option possible: " // name)
     283           6 :     else if (added_option%blank) then
     284           1 :       self%has_blank_option = .true.
     285             :     end if
     286             : 
     287          21 :     tmp_options = self%options
     288          21 :     do i = 1, size(tmp_options)
     289          15 :       if (tmp_options(i)%name == added_option%name) &
     290           0 :         call error_message("cli_parser%add_option: name already present: " // added_option%name)
     291             :       if (tmp_options(i)%has_s_name .and. added_option%has_s_name &
     292          15 :           .and. (tmp_options(i)%s_name == added_option%s_name)) &
     293           6 :         call error_message("cli_parser%add_option: short name already present: " // added_option%s_name)
     294             :     end do
     295             : 
     296          21 :     deallocate(self%options)
     297          39 :     allocate(self%options(size(tmp_options) + 1))
     298          21 :     self%options(1:size(tmp_options)) = tmp_options
     299           6 :     self%options(size(tmp_options) + 1) = added_option
     300             : 
     301         102 :   end subroutine add_option
     302             : 
     303             :   !> \brief Get \ref option count from the \ref cli_parser.
     304             :   !> \return Option count.
     305           9 :   integer(i4) function cnt_options(self)
     306             :     implicit none
     307             :     class(cli_parser), intent(inout) :: self
     308             : 
     309           0 :     cnt_options = size(self%options)
     310             : 
     311          12 :   end function cnt_options
     312             : 
     313             :   !> \brief check if this \ref option is the given argument.
     314             :   !> \return Truth value if the given argument is this \ref option.
     315           0 :   logical function is_given_arg(self, arg)
     316             :     implicit none
     317             :     class(option), intent(inout) :: self
     318             :     character(*), intent(in) :: arg
     319             : 
     320           0 :     is_given_arg = (arg == "--" // self%name) .or. (arg == "-" // self%s_name)
     321             : 
     322           9 :   end function is_given_arg
     323             : 
     324             :   !> \brief Get the \ref option index from \ref cli_parser by name.
     325             :   !> \return The desired \ref option index.
     326           6 :   integer(i4) function get_option_index(self, name, long, short, raise_error)
     327             :     implicit none
     328             :     class(cli_parser), intent(inout) :: self
     329             :     character(*), intent(in) :: name !< name of the desired option
     330             :     logical, intent(in), optional :: long !< whether to check long name (default: .true.)
     331             :     logical, intent(in), optional :: short !< whether to check short name (default: .true.)
     332             :     logical, intent(in), optional :: raise_error !< whether to raise an error if option is not found (default: .true.)
     333             : 
     334             :     integer(i4) :: i
     335             :     logical :: raise_error_, long_, short_
     336             : 
     337           6 :     raise_error_ = .true.
     338           6 :     long_ = .true.
     339           6 :     short_ = .true.
     340           0 :     if ( present(raise_error) ) raise_error_ = raise_error
     341           6 :     if ( present(long) ) long_ = long
     342           6 :     if ( present(short) ) short_ = short
     343             : 
     344             :     ! find the corresponding argument
     345           6 :     get_option_index = 0_i4
     346          21 :     do i = 1, self%cnt_options()
     347          21 :       if ((long_ .and. self%options(i)%name == name) .or. (short_ .and. self%options(i)%s_name == name)) then
     348             :         get_option_index = i
     349             :         exit
     350             :       end if
     351             :     end do
     352             : 
     353           6 :     if (get_option_index == 0_i4 .and. raise_error_) call error_message("cli_parser: unknown option: " // name)
     354             : 
     355           0 :   end function get_option_index
     356             : 
     357             :   !> \brief Get an \ref option from \ref cli_parser by name.
     358             :   !> \return The desired \ref option.
     359           5 :   type(option) function get_option(self, name)
     360             :     implicit none
     361             :     class(cli_parser), intent(inout) :: self
     362             :     character(*), intent(in) :: name !< name (long or short) of the desired option
     363             : 
     364             :     integer(i4) :: i
     365             : 
     366          10 :     i = self%get_option_index(name)
     367           5 :     get_option = self%options(i)
     368             : 
     369           6 :   end function get_option
     370             : 
     371             :   !> \brief Whether the \ref option was read by the \ref cli_parser given by name.
     372             :   !> \return Truth value if the given \ref option was read.
     373           5 :   logical function option_was_read(self, name)
     374             :     implicit none
     375             :     class(cli_parser), intent(inout) :: self
     376             :     character(*), intent(in) :: name !< name of the desired option
     377             : 
     378           5 :     type(option) :: opt
     379             : 
     380           5 :     opt = self%get_option(name)
     381           5 :     option_was_read = opt%was_read
     382             : 
     383          10 :   end function option_was_read
     384             : 
     385             :   !> \brief Read count for the \ref option in the \ref cli_parser given by name.
     386             :   !> \return Number of reads for the \ref option.
     387           0 :   integer(i4) function option_read_count(self, name)
     388             :     implicit none
     389             :     class(cli_parser), intent(inout) :: self
     390             :     character(*), intent(in) :: name !< name of the desired option
     391             : 
     392           0 :     type(option) :: opt
     393             : 
     394           0 :     opt = self%get_option(name)
     395           0 :     option_read_count = opt%read_count
     396             : 
     397           5 :   end function option_read_count
     398             : 
     399             :   !> \brief Whether the \ref option is defined in \ref cli_parser given by name.
     400             :   !> \return Truth value if the given \ref option was defined.
     401           0 :   logical function has_option(self, name)
     402             :     implicit none
     403             :     class(cli_parser), intent(inout) :: self
     404             :     character(*), intent(in) :: name !< name of the desired option
     405             : 
     406           0 :     has_option = self%get_option_index(name, raise_error=.false.) > 0
     407             : 
     408           0 :   end function has_option
     409             : 
     410             :   !> \brief Get the index of the blank \ref option.
     411             :   !> \return The desired \ref option index.
     412           1 :   integer(i4) function get_blank_option_index(self)
     413             :     implicit none
     414             :     class(cli_parser), intent(inout) :: self
     415             : 
     416             :     integer(i4) :: i
     417             : 
     418           1 :     if (.not. self%has_blank_option) &
     419           0 :       call error_message("cli_parser%get_blank_option_index: no blank option defined.")
     420             : 
     421             :     ! find the corresponding argument
     422           5 :     do i = 1, self%cnt_options()
     423           5 :       if (self%options(i)%blank) then
     424             :         get_blank_option_index = i
     425             :         exit
     426             :       end if
     427             :     end do
     428             : 
     429           0 :   end function get_blank_option_index
     430             : 
     431             :   !> \brief Get the parsed value from an \ref option by name from the \ref cli_parser.
     432             :   !> \return Value of the given \ref option.
     433           0 :   function option_value(self, name)
     434             :     implicit none
     435             :     class(cli_parser), intent(inout) :: self
     436             :     character(*), intent(in) :: name !< name of the desired option
     437             : 
     438             :     character(:), allocatable :: option_value
     439           0 :     type(option) :: opt
     440             : 
     441           0 :     opt = self%get_option(name)
     442           0 :     if (.not. opt%has_value) &
     443           0 :       call error_message("cli_parser%option_value: option has no value: " // name)
     444           0 :     option_value = opt%value
     445             : 
     446           1 :   end function option_value
     447             : 
     448             :   !> \brief Print info for an \ref option.
     449           0 :   subroutine print_info(self)
     450             :     implicit none
     451             :     class(option), intent(inout) :: self
     452             : 
     453           0 :     character(:), allocatable :: opt_str
     454             : 
     455             :     ! default values
     456           0 :     opt_str = ""
     457           0 :     if (self%blank) then
     458           0 :       opt_str = "  <" // self%value_name // ">"
     459             :     else
     460           0 :       opt_str = "  --" // self%name
     461           0 :       if (self%has_s_name) opt_str = opt_str // " / -" // self%s_name
     462           0 :       if (self%has_value) opt_str = opt_str // " <" // self%value_name // ">"
     463             :     end if
     464             : 
     465           0 :     call message(opt_str)
     466           0 :     call message("      Description: ", self%help)
     467           0 :     if (self%has_default) call message("      Default: ", self%default)
     468           0 :     if (self%repeated) call message("      Can be repeated.")
     469           0 :     if (self%required) call message("      (required)")
     470             : 
     471           0 :   end subroutine print_info
     472             : 
     473             :   !> \brief Print help message for the \ref cli_parser.
     474           0 :   subroutine print_help(self)
     475             :     implicit none
     476             :     class(cli_parser), intent(inout) :: self
     477             : 
     478             :     integer(i4) :: i
     479           0 :     character(:), allocatable :: blank_str
     480             : 
     481           0 :     blank_str = ""
     482           0 :     if (self%has_blank_option) blank_str = " <" // self%options(self%get_blank_option_index())%value_name // ">"
     483             : 
     484           0 :     call message(self%description)
     485           0 :     call message("")
     486           0 :     call message("  Usage: ", self%prog, " [options]", blank_str)
     487           0 :     call message("")
     488           0 :     call message("Options:")
     489             : 
     490             :     ! blank option
     491           0 :     if (self%has_blank_option) call self%options(self%get_blank_option_index())%print_info
     492             : 
     493             :     ! required
     494           0 :     do i = 1, self%cnt_options()
     495           0 :       if ((.not. self%options(i)%required) .or. self%options(i)%blank) cycle
     496           0 :       call message("")
     497           0 :       call self%options(i)%print_info
     498             :     end do
     499             : 
     500             :     ! optional
     501           0 :     do i = 1, self%cnt_options()
     502           0 :       if (self%options(i)%required .or. self%options(i)%blank) cycle
     503           0 :       call message("")
     504           0 :       call self%options(i)%print_info
     505             :     end do
     506             : 
     507           0 :   end subroutine print_help
     508             : 
     509             :   !> \brief Parse the given command line arguments with the \ref cli_parser.
     510           1 :   subroutine parse(self)
     511           0 :     use mo_logging, only: log_set_config
     512             :     implicit none
     513             :     class(cli_parser), intent(inout) :: self
     514             : 
     515             :     logical :: is_multi, long
     516             :     integer(i4) :: i, j, id, n
     517           1 :     character(:), allocatable :: arg, val, err_name, names(:)
     518           1 :     integer(i4), allocatable :: counts(:)
     519             : 
     520           1 :     i = 1_i4
     521           2 :     arg_loop: do while (i <= command_argument_count())
     522           1 :       call get_command_argument(i, length=n)
     523           1 :       if (allocated(arg)) deallocate(arg)
     524           1 :       allocate(character(n) :: arg)
     525           1 :       call get_command_argument(i, value=arg)
     526             :       ! arguments need to start with "-"
     527           1 :       if (.not. arg(1:1) == "-") then
     528           0 :         if (self%has_blank_option .and. i == command_argument_count()) then
     529           0 :           self%options(self%get_blank_option_index())%was_read = .true.
     530           0 :           self%options(self%get_blank_option_index())%value = arg
     531             :           exit arg_loop
     532             :         else
     533           0 :           call error_message("cli_parser%parse: unknown argument: " // arg)
     534             :         end if
     535             :       end if
     536             :       ! check for repeated values with short name (-ooo)
     537           1 :       call parse_arg(arg, names, counts)
     538           1 :       long = arg(2:2) == "-" ! after parse_arg, we know size(arg) > 1
     539           2 :       is_multi = sum(counts) > 1
     540           2 :       do j = 1, size(names)
     541             :         ! will raise an error if option not present
     542           1 :         id = self%get_option_index(names(j), long=long, short=.not.long)
     543             :         ! check repeatedly read options
     544           1 :         if ((counts(j) > 1 .or. self%options(id)%was_read) .and. .not.self%options(id)%repeated) &
     545           0 :           call error_message("cli_parser%parse: option given multiple times: " // self%options(id)%name)
     546             :         ! update read counts
     547           1 :         self%options(id)%was_read = .true.
     548           1 :         self%options(id)%read_count = self%options(id)%read_count + counts(j)
     549             :         ! check for value
     550           2 :         if (self%options(id)%has_value) then
     551           0 :           if ( is_multi ) &
     552           0 :             call error_message("cli_parser%parse: option expects a value: " // self%options(id)%name)
     553           0 :           if (i == command_argument_count()) &
     554           0 :             call error_message("cli_parser%parse: required value missing for: " // self%options(id)%name)
     555           0 :           call get_command_argument(i + 1, length=n)
     556           0 :           if (allocated(val)) deallocate(val)
     557           0 :           allocate(character(n) :: val)
     558           0 :           call get_command_argument(i + 1, value=val)
     559           0 :           self%options(id)%value = val
     560           0 :           i = i + 1
     561             :         end if
     562             :       end do
     563           1 :       i = i + 1
     564           4 :       deallocate(names, counts)
     565             :     end do arg_loop
     566             : 
     567           1 :     if (self%has_help) then
     568           1 :       if (self%option_was_read("help")) then
     569           0 :         call self%print_help()
     570           0 :         stop
     571             :       end if
     572             :     end if
     573             : 
     574           1 :     if (self%has_version) then
     575           1 :       if (self%option_was_read("version")) then
     576           0 :         call message(self%version)
     577           0 :         stop
     578             :       end if
     579             :     end if
     580             : 
     581             :     ! check for required parameters after help and version
     582           7 :     check_req: do j = 1, self%cnt_options()
     583           6 :       if ((.not. self%options(j)%was_read) .and. self%options(j)%has_default) then
     584           1 :         self%options(j)%value = self%options(j)%default
     585           1 :         self%options(j)%was_read = .true.
     586             :       end if
     587           7 :       if (self%options(j)%required .and. (.not. self%options(j)%was_read)) then
     588           0 :         if (self%options(j)%blank) then
     589           0 :           err_name = "<" // self%options(j)%value_name // ">"
     590             :         else
     591           0 :           err_name = "--" // self%options(j)%name
     592             :         end if
     593           0 :         call error_message("cli_parser%parse: required option missing: " // err_name)
     594             :       end if
     595             :     end do check_req
     596             : 
     597             :     ! set logger
     598           1 :     if ( self%has_logger ) then
     599             :       call log_set_config( &
     600             :         verbose = self%option_read_count("verbose"), &
     601             :         quiet = self%option_read_count("quiet"), &
     602             :         log_output_hostname = self%option_was_read("log-output-hostname"), &
     603             :         log_force_colors = self%option_was_read("log-force-colors"), &
     604             :         log_no_colors = self%option_was_read("log-no-colors"), &
     605             :         log_no_format = self%option_was_read("log-no-format"), &
     606             :         log_output_date = self%option_was_read("log-output-date"), &
     607             :         log_output_time = self%option_was_read("log-output-time") &
     608           0 :       )
     609             :     end if
     610             : 
     611           1 :   end subroutine parse
     612             : 
     613             :   !> \brief Parse given argument.
     614             :   !> \details Parse a given argument, that starts with an "-", to determine the involved options in case of a multi arg (-xyz).
     615           1 :   subroutine parse_arg(arg, names, counts)
     616           1 :     use mo_append, only: append
     617             :     implicit none
     618             :     character(*), intent(in) :: arg
     619             :     character(:), intent(out), allocatable :: names(:) !< names of involved options (can be multiple by using combined short names)
     620             :     integer(i4), intent(out), allocatable :: counts(:) !< counts of occurrences of each option
     621             : 
     622           1 :     character, allocatable :: s_names(:) ! needed for "append"
     623             :     integer(i4) :: i, j
     624             : 
     625           0 :     if ( arg(1:1) /= "-" ) call error_message("cli_parser%parse: invalid argument: " // arg)
     626           1 :     if ( len(arg) < 2 ) call error_message("cli_parser%parse: found empty argument: " // arg)
     627             : 
     628             :     ! check for long name (--name)
     629           1 :     if ( arg(2:2) == "-" ) then
     630           1 :       if ( len(arg) == 2 ) call error_message("cli_parser%parse: found empty argument: " // arg)
     631           1 :       allocate(character(len(arg)-2) :: names(1))
     632           1 :       names(1) = arg(3:len(arg))
     633           1 :       call append(counts, 1_i4)
     634           1 :       return
     635             :     end if
     636             : 
     637           0 :     call append(s_names, arg(2:2))
     638           0 :     call append(counts, 1_i4)
     639           0 :     do i=3, len(arg)
     640             :       ! check if name was already present in this multi option
     641           0 :       j = findchar(s_names, arg(i:i))
     642           0 :       if ( j == 0 ) then
     643           0 :         call append(s_names, arg(i:i))
     644           0 :         call append(counts, 1_i4)
     645             :       else
     646           0 :         counts(j) = counts(j) + 1_i4
     647             :       end if
     648             :     end do
     649           0 :     allocate(character(1) :: names(size(s_names)))
     650           0 :     names = s_names
     651           2 :   end subroutine parse_arg
     652             : 
     653           0 :   integer(i4) function findchar(array, chr)
     654             :     character, intent(in) :: array(:)
     655             :     character, intent(in) :: chr
     656             : 
     657             :     integer(i4) :: i
     658             : 
     659           0 :     findchar = 0_i4
     660           0 :     do i = 1, size(array)
     661           0 :       if (array(i) == chr) then
     662           0 :         findchar = i
     663           0 :         return
     664             :       end if
     665             :     end do
     666             : 
     667           1 :   end function findchar
     668             : 
     669           0 : end module mo_cli

Generated by: LCOV version 1.16