source: trunk/LMDZ.TITAN/libf/muphytitan/argparse.F90 @ 3026

Last change on this file since 3026 was 1897, checked in by jvatant, 7 years ago

Making Titan's hazy again - part II
+ Major updates of J.Burgalat YAMMS library and optical coupling, including :
++ Added the routines for haze optics inside YAMMS
++ Calling rad. transf. with interactive haze is plugged
in but should stay unactive as long as the microphysics is
in test phase : cf "uncoupl_optic_haze" flag : true for now !
++ Also some sanity checks for negative tendencies and
some others upkeep of YAMMS model
+ Also added a temporary CPP key USE_QTEST in physiq_mod
that enables to have microphysical tendencies separated
from dynamics for debugging and test phases
-- JVO and JB

File size: 116.3 KB
Line 
1! Copyright Jérémie Burgalat (2010-2015,2017)
2!
3! jeremie.burgalat@univ-reims.fr
4!
5! This software is a computer program whose purpose is to provide configuration
6! file and command line arguments parsing features to Fortran programs.
7!
8! This software is governed by the CeCILL-B license under French law and
9! abiding by the rules of distribution of free software.  You can  use,
10! modify and/ or redistribute the software under the terms of the CeCILL-B
11! license as circulated by CEA, CNRS and INRIA at the following URL
12! "http://www.cecill.info".
13!
14! As a counterpart to the access to the source code and  rights to copy,
15! modify and redistribute granted by the license, users are provided only
16! with a limited warranty  and the software's author,  the holder of the
17! economic rights,  and the successive licensors  have only  limited
18! liability.
19!
20! In this respect, the user's attention is drawn to the risks associated
21! with loading,  using,  modifying and/or developing or reproducing the
22! software by the user in light of its specific status of free software,
23! that may mean  that it is complicated to manipulate,  and  that  also
24! therefore means  that it is reserved for developers  and  experienced
25! professionals having in-depth computer knowledge. Users are therefore
26! encouraged to load and test the software's suitability as regards their
27! requirements in conditions enabling the security of their systems and/or
28! data to be ensured and,  more generally, to use and operate it in the
29! same conditions as regards security.
30!
31! The fact that you are presently reading this means that you have had
32! knowledge of the CeCILL-B license and that you accept its terms.
33
34!! file: argparse.F90
35!! summary: Command-line parser source file.
36!! author: J. Burgalat
37!! date: 2013-2015,2017
38
39#include "defined.h"
40
41MODULE ARGPARSE
42  !> Command-line parsing module
43  !!
44  !! Here are described all the public members of argparse module.
45  !! For your own sanity, private methods that call Ancient Gods powers through
46  !! evil black magic rituals are not described here.
47  !!
48  !! If you only wish to have an overview of argparse usage, you'd better go
49  !! [here](|url|/page/swift/p01_argparse.html).
50
51  USE, INTRINSIC :: ISO_FORTRAN_ENV, ONLY : stdout=>OUTPUT_UNIT, stderr=>ERROR_UNIT
52  USE ERRORS
53  USE FSYSTEM, ONLY : fs_termsize
54  USE STRING_OP, getpar => format_paragraph, splitstr  => format_string 
55  IMPLICIT NONE
56
57  PRIVATE
58
59  ! Public members and imported features
60  ! from errors: export everything (operator are exported latter)
61  PUBLIC :: noerror,error, error_to_string,aborting
62  ! from strings
63  PUBLIC :: st_slen, st_llen
64  PUBLIC :: stderr, stdout
65  ! argparse module
66  PUBLIC :: new_argparser,              &
67            argparser_clear,            &
68            argparser_add_option,       &
69            argparser_add_positionals,  &
70            argparser_throw_error,      &
71            argparser_parse,            &
72            argparser_help,             &
73            argparser_get_positional,   &
74            argparser_get_value,        &
75            argparser_reset_values,     &
76            argparser_found,            &
77            argparser_get_num_values,   &
78            argparser_found_positional, &
79            argparser_get_num_positional
80
81  PUBLIC :: OPERATOR(==), OPERATOR(/=), ASSIGNMENT(=)
82
83  ! ===========================
84  ! PARAMETERS (INTRISIC TYPES)
85  ! ===========================
86
87  INTEGER, PARAMETER, PUBLIC :: ap_string  = st_string
88    !! String value type identifier.
89  INTEGER, PARAMETER, PUBLIC :: ap_complex = st_complex
90    !! Complex value type identifier.
91  INTEGER, PARAMETER, PUBLIC :: ap_logical = st_logical
92    !! Logical value type identifier.
93  INTEGER, PARAMETER, PUBLIC :: ap_integer = st_integer
94    !! Integer value type identifier.
95  INTEGER, PARAMETER, PUBLIC :: ap_real = st_real
96    !! Real value type identifier.
97
98  !> List of all available actions
99
100  INTEGER, PARAMETER, PUBLIC :: ap_store  = 1
101    !! store action ID : Each time the option is seen, values are replaced.
102  INTEGER, PARAMETER, PUBLIC :: ap_append = 2
103    !! append action ID : Each time the option is seen, values are appended.
104  INTEGER, PARAMETER, PUBLIC :: ap_count  = 3
105    !! count action ID : increase a counter each time the option is seen.
106  INTEGER, PARAMETER, PUBLIC :: ap_help   = 4
107    !! help action ID : help is requested !
108
109  !> List of all available actions
110  INTEGER, DIMENSION(4), PARAMETER, PRIVATE :: ap_actions = (/ap_store,  &
111                                                              ap_append, &
112                                                              ap_count,  &
113                                                              ap_help/)
114  !> List of all recognized types by the parser
115  INTEGER, DIMENSION(5), PARAMETER, PRIVATE :: ap_types = (/ap_string,  &
116                                                            ap_logical, &
117                                                            ap_complex, &
118                                                            ap_integer, &
119                                                            ap_real/)
120  !> The unknown flag
121  !!
122  !! This flag is only intended to initialize flags. It is set by default during initialization
123  !! and quielty replaced by default flags, if user does not provide the relevant feature.
124  INTEGER, PARAMETER :: ap_undef = -1
125   
126  !> Add an option to the parser
127  !!
128  !! ```
129  !! FUNCTION argparser_add_option(this,dest,sflag,lflag,type,action,default,nrec,help,meta) RESULT(err)
130  !!          argparser_add_option(this,dest,flag,type,action,default,nrec,help,meta) RESULT(err)
131  !! ```
132  !!
133  !! The function defines a new argument based on input parameters, checks it and finally sets it
134  !! in the parser.
135  !!
136  !! In its first version both short (`sflag`) and long (`lflag`) options flags are mandatory. In its second
137  !! form, a single flag (`flag`) is expected: the method will automatically deduce if it belongs to short or
138  !! a long option flag based on the number of hyphens given.
139  !!
140  !! `type` value should be one of the following module constants (which are aliases from [[string_op(module)]]):
141  !!
142  !! - `ap_string` ([[string_op(module):st_string(variable)]])
143  !! - `ap_complex` ([[string_op(module):st_complex(variable)]])
144  !! - `ap_logical` ([[string_op(module):st_logical(variable)]])
145  !! - `ap_integer` ([[string_op(module):st_integer(variable)]])
146  !! - `ap_real` ([[string_op(module):st_real(variable)]])
147  !!
148  !! `action` value should be one of the following module constants:
149  !!
150  !! - [[argparse(module):ap_store(variable)]]
151  !! - [[argparse(module):ap_append(variable)]]
152  !! - [[argparse(module):ap_count(variable)]]
153  !! - [[argparse(module):ap_help(variable)]]
154  !!
155  !! `nrec` string can take the following forms:
156  !!
157  !! tag   | description
158  !! :---: | : -------------
159  !!  "?"  | zero or one argument's value
160  !!  "*"  | any number of arguments
161  !!  "+"  | one or more argument's value(s)
162  !!  "X"  | Exactly X values. Where X is the string representation of an integer (0 is accepted).
163  !!
164  !! On success, `noerror` is returned. Otherwise -9 error code is returned. Errors are only
165  !! produced by misuse of the function arguments. In such case, the program should be
166  !! stopped: note that such error should not occur in _released_ programs.
167  INTERFACE argparser_add_option
168    MODULE PROCEDURE ap_add_option_1, ap_add_option_2
169  END INTERFACE
170 
171  !> Get positional argument value(s)
172  INTERFACE argparser_get_positional
173    MODULE PROCEDURE ap_get_positional_sc, ap_get_positional_ve
174  END INTERFACE
175
176  !> Get optional argument value(s)
177  !!
178  !! ```
179  !! FUNCTION argparser_get_value(this,name,output) RESULT(err)
180  !! ```
181  !!
182  !! This is the generic method that can be used to retrieve any kind of argument value(s) from the parser for a given
183  !! argument name (as defined by the `dest` argument of [[argparse(module):argparser_add_option(interface)]].
184  !! All the methods have the same dummy arguments only `output` dummy argument differs in type and shape.
185  !!
186  !! @note
187  !! For string vector, `output` is expected to be an allocatable vector of **assumed length**
188  !! strings (thus string length is left to user responsability).
189  !! A good compromise for strings length is to use the [[string_op(module):st_slen(variable)]]
190  !! parameter.
191  INTERFACE argparser_get_value
192    MODULE PROCEDURE ap_get_dv_sc, ap_get_rv_sc, ap_get_iv_sc, ap_get_lv_sc, &
193                     ap_get_cv_sc, ap_get_sv_sc, ap_get_dv_ve, ap_get_rv_ve, &
194                     ap_get_iv_ve, ap_get_lv_ve, ap_get_cv_ve, ap_get_sv_ve
195  END INTERFACE
196
197  !> Interface to [[argparse(module):argc(type)]] getters
198  !!
199  !! All the functions have the same prototype, only kind and type of arguments changed
200  !! from a function to the other.
201  INTERFACE argc_get_value                   
202    MODULE PROCEDURE ac_get_dv_sc, ac_get_rv_sc, ac_get_iv_sc, ac_get_lv_sc, &
203                     ac_get_cv_sc, ac_get_sv_sc, ac_get_dv_ve, ac_get_rv_ve, &
204                     ac_get_iv_ve, ac_get_lv_ve, ac_get_cv_ve, ac_get_sv_ve
205  END INTERFACE
206
207  !> argc equality operator
208  INTERFACE OPERATOR(==)
209    MODULE PROCEDURE ac_equals_arg
210  END INTERFACE
211
212  !> argc inequality operator
213  INTERFACE OPERATOR(/=)
214    MODULE PROCEDURE ac_differs_arg
215  END INTERFACE
216
217  !> argc assignment statement
218  INTERFACE ASSIGNMENT(=)
219    MODULE PROCEDURE ac_affect_arg
220    MODULE PROCEDURE ap_affect_parser
221  END INTERFACE
222
223  !> argc *destructors* interface
224  INTERFACE clear_argc
225    MODULE PROCEDURE ac_clear_arg_sc, ac_clear_arg_ve
226  END INTERFACE
227
228
229  TYPE, PRIVATE :: argc
230    !! Defines a command-line argument.
231    !!
232    !! An [[argparse(module):argc(type)]] object stores all information about a command-line
233    !! argument, that is:
234    !!
235    !! - its name
236    !! - its optional flags
237    !! - its type
238    !! - its action
239    !! - and finally its values
240    PRIVATE
241    INTEGER          :: ptype = ap_logical
242      !! Type flag (an integer from enum argparse::ap_types)
243    INTEGER          :: paction = ap_store
244      !! Action flag (an integer from enum argparse::ap_actions)
245    INTEGER          :: nrec = 0
246      !! Number of values
247    LOGICAL          :: fnd = .false.
248      !! A boolean flag set to `.true.` if argument has been found in the command-line.
249    TYPE(words)      :: values
250      !! Values of the argument
251    CHARACTER(len=2) :: sflag = "  "
252      !! Short flag option
253    TYPE(words)      :: meta
254      !! Meta variable name(s) of the argument
255#if HAVE_FTNDTSTR
256    CHARACTER(len=:), ALLOCATABLE :: default
257      !! Default flag
258    CHARACTER(len=:), ALLOCATABLE :: name
259      !! Name of the argument (needed to check and retrieve its value(s))
260    CHARACTER(len=:), ALLOCATABLE :: lflag
261      !! Long flag option (st_short_len max chars !)
262    CHARACTER(len=:), ALLOCATABLE :: help
263      !! Help about the argument
264#else
265    CHARACTER(len=st_slen) :: default = ""
266      !! Default flag
267    CHARACTER(len=st_slen) :: name
268      !! Name of the argument (needed to check and retrieve its value(s))
269    CHARACTER(len=st_slen) :: lflag = ""
270      !! Long flag option (st_short_len max chars !)
271    CHARACTER(len = 200)   :: help = ""
272      !! Help about the argument
273#endif
274  END TYPE argc
275
276
277  TYPE, PUBLIC :: argparser
278    !! Command-line parser
279    !!
280    !! This is the main object of the module. It stores definitions of CLI arguments and
281    !! their value(s) once the command-line have been parsed.
282    TYPE(argc), PRIVATE, ALLOCATABLE, DIMENSION(:) :: args
283      !! List of defined arguments
284    INTEGER, PRIVATE :: nargs = 0
285      !! Size of args
286    INTEGER, PRIVATE :: parsed = -1
287      !! Parsing control flag
288      !!
289      !! The parsing flag determines if the command line have been parsed :
290      !!
291      !!   - -1 : not parsed yet
292      !!   - 0  : unsuccessfully parsed
293      !!   - 1  : successfully parsed
294    TYPE(argc), PRIVATE :: posals
295      !! Positionals arguments (defined as a single argc object)
296    LOGICAL, PRIVATE :: have_posal = .false.
297      !! Positional control flag
298#if HAVE_FTNDTSTR
299    CHARACTER(len=:), PRIVATE, ALLOCATABLE :: usg
300      !! Program command usage
301    CHARACTER(len=:), PRIVATE, ALLOCATABLE :: descr
302      !! Program help description
303    CHARACTER(len=:), PRIVATE, ALLOCATABLE :: eplg
304      !! Program help epilog
305#else
306    CHARACTER(len=st_llen), PRIVATE :: usg
307      !! Program command usage
308    CHARACTER(len=st_llen), PRIVATE :: descr
309      !! Program help description
310    CHARACTER(len=st_llen), PRIVATE :: eplg
311      !! Program help epilog
312#endif
313    INTEGER, PRIVATE :: mxhlpos = 20
314      !! Position of the short help for options
315    INTEGER, PRIVATE :: width = 0
316      !! Maximum width of the help
317    LOGICAL, PRIVATE :: init = .false.
318      !! Initialization control flag
319#if HAVE_FTNPROC   
320
321    CONTAINS
322    PROCEDURE, PRIVATE :: ap_add_option_1
323    PROCEDURE, PRIVATE :: ap_add_option_2
324    PROCEDURE, PRIVATE :: ap_get_positional_sc
325    PROCEDURE, PRIVATE :: ap_get_positional_ve
326    PROCEDURE, PRIVATE :: ap_get_dv_sc
327    PROCEDURE, PRIVATE :: ap_get_rv_sc
328    PROCEDURE, PRIVATE :: ap_get_iv_sc
329    PROCEDURE, PRIVATE :: ap_get_lv_sc
330    PROCEDURE, PRIVATE :: ap_get_cv_sc
331    PROCEDURE, PRIVATE :: ap_get_sv_sc
332    PROCEDURE, PRIVATE :: ap_get_dv_ve
333    PROCEDURE, PRIVATE :: ap_get_rv_ve
334    PROCEDURE, PRIVATE :: ap_get_iv_ve
335    PROCEDURE, PRIVATE :: ap_get_lv_ve
336    PROCEDURE, PRIVATE :: ap_get_cv_ve
337    PROCEDURE, PRIVATE :: ap_get_sv_ve
338    PROCEDURE, PRIVATE :: ap_check_state
339    PROCEDURE, PUBLIC  :: throw_error        => argparser_throw_error
340      !! Throw an error and exit the program
341    PROCEDURE, PUBLIC  :: parse              => argparser_parse
342      !! Parse the command-line (or the given input string).
343    PROCEDURE, PUBLIC  :: help               => argparser_help 
344      !! Compute and print help
345    PROCEDURE, PUBLIC  :: found              => argparser_found
346      !! Check if an optional argument has been found on the command-line
347    PROCEDURE, PUBLIC  :: get_num_values     => argparser_get_num_values
348      !! Get the actual number of values stored in an argument.
349    PROCEDURE, PUBLIC  :: found_positional   => argparser_found_positional
350      !! Check if positional argument(s) has been found on the command-line
351    PROCEDURE, PUBLIC  :: get_num_positional => argparser_get_num_positional
352      !! Get the actual number of values stored as positionals.
353    PROCEDURE, PUBLIC  :: add_positionals    => argparser_add_positionals
354      !! Add positionals definitions in the parser.
355    !> Add optional argument definition in the parser.
356    GENERIC, PUBLIC    :: add_option         => ap_add_option_1, &
357                                                ap_add_option_2
358    !> Get the values of the positionals stored in the parser.                                               
359    GENERIC, PUBLIC    :: get_positional     => ap_get_positional_sc, &
360                                                ap_get_positional_ve
361    !> Get the value(s) of the given argument stored in the parser.
362    GENERIC, PUBLIC    :: get_value          => ap_get_dv_sc, &
363                                                ap_get_rv_sc, &
364                                                ap_get_iv_sc, &
365                                                ap_get_lv_sc, &
366                                                ap_get_cv_sc, &
367                                                ap_get_sv_sc, &
368                                                ap_get_dv_ve, &
369                                                ap_get_rv_ve, &
370                                                ap_get_iv_ve, &
371                                                ap_get_lv_ve, &
372                                                ap_get_cv_ve, &
373                                                ap_get_sv_ve
374#endif       
375  END TYPE argparser
376
377  CONTAINS
378
379  ! argparser main methods (public)
380  ! -------------------------------
381
382  FUNCTION new_argparser(usg, dsc, epg, add_help, width, max_help_pos) RESULT(this)
383    !! Initialize an argparser object.
384    !!
385    !! The method initializes (properly) an [[argparse(module):argparser(type)]] object.
386    !! Even if all the arguments are optional, it is mandatory to **call** the method
387    !! before using an argparser object.
388    CHARACTER(len=*), INTENT(in), OPTIONAL :: usg
389      !! An optional string with the command line usage of the program. If it is not given
390      !! command-line usage is automatically built from informations set in the parser.
391    CHARACTER(len=*), INTENT(in), OPTIONAL :: dsc
392      !! An optional string with the short description of the program.
393    CHARACTER(len=*), INTENT(in), OPTIONAL :: epg
394      !! An optional string with the epilog of the program's help
395    LOGICAL, INTENT(in), OPTIONAL          :: add_help
396      !! An optional boolean flag with `.true.` to automatically set an option for program's help.
397      !! Note that, the option flags `-h` and `--help` are no more available in that case.
398    INTEGER, INTENT(in), OPTIONAL          :: width
399      !! An optional integer with the maximum width the help text.
400    INTEGER, INTENT(in), OPTIONAL          :: max_help_pos
401      !! An optional integer with the maximum position of the help string for each option of
402      !! the program when help is requested. Note that this value is just an indicator. The
403      !! helper computes the minimum position between this value and the maximum length of the
404      !! options flags.
405    TYPE(argparser) :: this
406      !! An initialized argparse object.
407    INTEGER     :: zh
408    TYPE(error) :: err
409    ! We always clear the parser
410    CALL argparser_clear(this)
411    ! Set keywords
412    IF (PRESENT(usg)) THEN ; this%usg=usg   ; ELSE ; this%usg=''   ; ENDIF
413    IF (PRESENT(dsc)) THEN ; this%descr=dsc ; ELSE ; this%descr='' ; ENDIF
414    IF (PRESENT(epg)) THEN ; this%eplg=epg  ; ELSE ; this%eplg=''  ; ENDIF
415    CALL fs_termsize(zh,this%width)
416    IF (PRESENT(width)) this%width = MAX(width,50)
417    IF(PRESENT(max_help_pos)) this%mxhlpos = MAX(5,max_help_pos)
418    this%init = .true. ! before adding option !!!
419    IF (PRESENT(add_help)) THEN
420      IF (add_help) &
421        err = argparser_add_option(this,'help',sflag='-h',lflag='--help', &
422                    action=ap_help, help="Print this help and quit")
423    ENDIF
424    RETURN
425  END FUNCTION new_argparser
426
427  SUBROUTINE argparser_clear(this)
428    !! Clear the parser
429    !! The subroutine is used as finalization subroutine of argparser type.
430    !! Once the method is called, the object is no more usable until it is
431    !! (re)initialized by calling argparse::new_argparser.
432    !! @note If **fccp** has not been built with support for finalization subroutine,
433    !! it should be called whenever the argparser object is no more used.
434    TYPE(argparser), INTENT(inout) :: this
435      !! An argparser object
436    IF (ALLOCATED(this%args)) THEN
437      CALL clear_argc(this%args)
438      DEALLOCATE(this%args)
439    ENDIF
440    ! maybe we should should set this%posals as allocatable
441    CALL clear_argc(this%posals)
442    this%nargs      = 0
443    this%parsed     = -1
444    this%have_posal = .false.
445    this%usg        = ''
446    this%descr      = ''
447    this%eplg       = ''
448    this%mxhlpos    = 20
449    this%width      = 0
450    this%init       = .false.
451  END SUBROUTINE argparser_clear
452
453  SUBROUTINE argparser_reset_values(this)
454    !! Reset all arguments values in the parser
455    !! The method only deletes arguments value(s) currently stored in the parser.
456    OBJECT(argparser), INTENT(inout) :: this
457      !! An argparser object reference
458    ! Check if list is empty
459    IF (this%nargs == 0) RETURN
460    CALL words_clear(this%args(:)%values)
461    CALL words_clear(this%posals%values)
462  END SUBROUTINE argparser_reset_values
463
464  FUNCTION argparser_add_positionals(this,nargs,meta,help) RESULT(err)
465    !! Add positional arguments definition to the parser.
466    !!
467    !! The method initializes the entry for positional arguments in the parser.
468    !! Positional arguments are always seen by the parser as strings and the
469    !! default associated action is 'store'.
470    OBJECT(argparser), INTENT(inout)                     :: this
471      !! An argparser object reference
472    CHARACTER(len=*), INTENT(in)                         :: nargs
473      !! A string with the expected number of specified values for the option
474    CHARACTER(len=*), INTENT(in), DIMENSION(:), OPTIONAL :: meta
475      !! A vector of strings with the the displayed value name(s) of the positionals in the help command
476    CHARACTER(len=*), INTENT(in), OPTIONAL               :: help
477      !! An optional string with a short description of the positional argument(s)
478    TYPE(error) :: err
479      !! Error object with the first error encountered in the process.
480    INTEGER                       :: ty,ac
481    CHARACTER(len=:), ALLOCATABLE :: sf,lf,de
482    err = noerror
483    IF (.NOT.this%init) THEN
484      err = error("argparse: parser not initialized yet",-1)
485      RETURN
486    ENDIF
487    IF (this%have_posal) THEN
488      err = error('argparse: positionals arguments already defined',-8)
489      RETURN
490    ELSE
491      this%posals%name = 'positional'
492      sf = '  ' ; lf = '' ; ty = ap_string ; ac = ap_store ; de = ''
493      IF (PRESENT(help)) THEN
494        this%posals%help = TRIM(help)
495      ELSE
496        this%posals%help = ''
497      ENDIF
498      IF (PRESENT(meta)) THEN
499        err = ac_check_and_set(this%posals,sf,lf,ty,ac,de,nargs,meta,.false.)
500      ELSE
501        err = ac_check_and_set(this%posals,sf,lf,ty,ac,de,nargs,check_flag=.false.)
502      ENDIF
503      IF (err /= noerror) THEN
504        RETURN
505      ENDIF
506      this%have_posal = this%posals%nrec /= 0
507    ENDIF
508    RETURN
509  END FUNCTION argparser_add_positionals
510
511  FUNCTION argparser_parse(this,cmd_line,auto) RESULT(err)
512    !! Parse the command line
513    !! The method parses either the command-line or the string `cmd_line`
514    !! given as optional argument and fills the parser's arguments.
515    !! @note
516    !! If `cmd_line` is provided it should not contains the name of the program or
517    !! the parsing process will certainly failed: program name will be seen as the
518    !! first positional argument and all tokens of the string will then be seen as
519    !! positional.
520    OBJECT(argparser), INTENT(inout)       :: this
521      !! An argparser object reference
522    CHARACTER(len=*), INTENT(in), OPTIONAL :: cmd_line
523      !! An optional string to parse that substitute for the actual command-line.
524    LOGICAL, INTENT(in), OPTIONAL          :: auto
525      !! An optional boolean flag with `.true.` to instruct the parser wether to perform
526      !! automatic actions or not when error occur during parsing. If `auto` is enabled,
527      !! then the parser dumps program's usage and stops the program on error.
528    TYPE(error) :: err
529      !! Error object with the first error encountered in the process.
530    CHARACTER(len=:), ALLOCATABLE :: cline,z
531    LOGICAL                       :: zauto
532    LOGICAL                       :: rhelp
533    INTEGER                       :: l
534    TYPE(words)                   :: cmd_tokens
535    err = noerror
536    IF (.NOT.this%init)  THEN
537      err = error("parser not initialized yet",-1) ; RETURN
538    ENDIF
539    rhelp = .false.
540    zauto = .false. ; IF (PRESENT(auto)) zauto = auto
541    IF (PRESENT(cmd_line)) THEN
542      ALLOCATE(cline,source=cmd_line)
543    ELSE
544      CALL GET_COMMAND(length=l)
545      ALLOCATE(CHARACTER(len=l) :: z) ; CALL GET_COMMAND(z)
546      CALL GET_COMMAND_ARGUMENT(0,length=l)
547      IF (l >= LEN_TRIM(z)) THEN ; cline='' ; ELSE ; cline=z(l+1:LEN(z)) ; ENDIF
548      DEALLOCATE(z)
549    ENDIF
550    ! reset parsing status
551    this%parsed = -1
552    CALL argparser_reset_values(this)
553    DO
554      ! Do we have to launch the turbine ?
555      IF (LEN_TRIM(cline) == 0) THEN
556        IF (this%have_posal) err=error("Wrong number of arguments",-16)
557        EXIT ! ... No :)
558      ELSE
559        err = ap_split_cmd(this,cline,cmd_tokens,rhelp)
560        ! we only stops processing if :
561        !   - the internal error (string length) is raised
562        !   - help flag found AND auto has been set
563        IF (err /= noerror .OR. (rhelp.AND.zauto)) EXIT
564      ENDIF
565      CALL words_reset(cmd_tokens) ! not mandatory... at least theoretically
566      ! Parses the options
567      err = ap_parse_options(this,cmd_tokens,rhelp)
568      IF (err /= noerror) EXIT
569      ! exit loop if help is requested. Parser is not completely filled but we
570      ! expect someone to use the help action..
571      IF (rhelp) EXIT
572      ! Parses positionals
573      err = ap_parse_positionals(this,cmd_tokens)
574      EXIT ! A one iterated loop :)
575    ENDDO
576    IF (err /= 0) THEN
577      CALL argparser_reset_values(this)
578    ELSE
579      this%parsed = 1
580    ENDIF
581    IF (zauto) THEN
582      IF (rhelp) CALL argparser_help(this)
583      IF (err /= 0) CALL argparser_throw_error(this,err,2)
584    ENDIF
585    RETURN
586  END FUNCTION argparser_parse
587
588  SUBROUTINE argparser_help(this)
589    !! Print help and exit program
590    OBJECT(argparser), INTENT(inout) :: this
591      !! An argparser object reference
592    CHARACTER(len=:), ALLOCATABLE :: helpme
593    !!!! WARNING we set no indication here !!!
594    IF (.NOT.this%init) RETURN
595    helpme = ap_gen_help(this)
596
597    WRITE(stdout,'(a)') helpme
598
599    CALL argparser_clear(this)
600    ! Finally we exit the program
601    CALL EXIT(0)
602  END SUBROUTINE argparser_help
603
604  SUBROUTINE argparser_throw_error(this,err,exit_id)
605    !! Dump error on standard error and exit
606    !!
607    !! The method performs the following actions:
608    !! 
609    !! - Print the usage command of the program
610    !! - Dump the provided @p error message
611    !! - Call parser's clean-up subroutine (if a *cleaner* callback has been given during the
612    !!   parser's initialization, see [[argparse(module):new_argparser(function)]] documentation
613    !! - Stop the program
614    !!
615    !! The error message is always printed in standard error output.
616    !! @note
617    !! If errors::error::id is 0 the method does nothing.
618    OBJECT(argparser), INTENT(inout) :: this
619      !! An argparser object reference
620    TYPE(error), INTENT(in)          :: err
621      !! An error object with the error to print
622    INTEGER, INTENT(in), OPTIONAL    :: exit_id
623      !! An optional integer with the exit code (default to 2)
624    CHARACTER(len=:), ALLOCATABLE    :: pgn
625    TYPE(error) :: zerr
626    IF (err == 0) RETURN
627    zerr = error(err%msg,2)
628    IF (PRESENT(exit_id)) zerr%id=exit_id
629    CALL ap_format_usage(this)
630    WRITE(stderr,'(a)') TRIM(this%usg)//NEW_LINE('A')
631    ! clean the parser
632    CALL argparser_clear(this)
633    pgn = get_progname()
634    WRITE(stderr,'(a)') pgn//": error: "//TRIM(err%msg)
635    CALL EXIT(err%id)
636  END SUBROUTINE argparser_throw_error
637
638  FUNCTION argparser_found(this,argname) RESULT(found)
639    !! Check wether an argument has been found in the command-line.
640    !! @note
641    !! Keep in mind that arguments in the parser always have a default
642    !! value. This method is not intended to check if an argument has a value but
643    !! only if it has been seen on the command-line !
644    OBJECT(argparser), INTENT(in) :: this
645      !! An argparser object reference
646    CHARACTER(len=*), INTENT(in)  :: argname
647      !! Name of the argument to check
648    LOGICAL :: found
649      !! `.true.` if the option has been parsed, `.false.` otherwise
650    INTEGER  :: idx
651    idx = ap_get_arg_index(this,argname)
652    IF (idx == -1) THEN
653      found = .false.
654    ELSE
655      found = ac_found(this%args(idx))
656    ENDIF
657  END FUNCTION argparser_found
658
659  FUNCTION argparser_get_num_values(this,argname) RESULT(num)
660    !! Get the actual number of values stored in an argument.
661    OBJECT(argparser), INTENT(in) :: this
662      !! An argparser object reference
663    CHARACTER(len=*), INTENT(in)  :: argname
664      !! Name of the argument to check.
665    INTEGER :: num
666      !! The number of actual values stored in the argument
667    INTEGER  :: idx
668    idx = ap_get_arg_index(this,argname)
669    IF (idx == -1) THEN
670      num = 0
671    ELSE
672      num = words_length(this%args(idx)%values)
673    ENDIF
674  END FUNCTION argparser_get_num_values
675
676  FUNCTION argparser_found_positional(this) RESULT(ret)
677    !! Check if positional(s) has been found in the command line.
678    OBJECT(argparser), INTENT(in) :: this
679      !! An argparser object reference
680    LOGICAL :: ret
681    !! `.true.` if found, `.false.` otherwise
682    TYPE(error) :: err
683    ret = .false.
684    IF (this%have_posal) THEN
685      ret = this%posals%fnd
686    ENDIF
687  END FUNCTION argparser_found_positional
688
689  FUNCTION argparser_get_num_positional(this) RESULT(ret)
690    !! Get the actual number of positional argument values stored in the parser .
691    OBJECT(argparser), INTENT(in) :: this
692      !! An argparser object reference
693    INTEGER :: ret
694      !! The number of actual positionals arguments
695    ret = 0
696    IF (this%have_posal) THEN
697      ret = words_length(this%posals%values)
698    ENDIF
699  END FUNCTION argparser_get_num_positional
700
701  ! argparser private methods
702  ! -------------------------
703
704  FUNCTION ap_check_state(this) RESULT(err)
705    !! Check current parser state
706    !! The method returns an error based on the current parser's state:
707    !! - Parser is ready (0)
708    !! - parsing not done yet (-19)
709    !! - parsing (already) failed (-20)
710    !! - parser is **NOT** initialized (-1)
711    OBJECT(argparser), INTENT(in) :: this
712      !! An argparser object reference
713    TYPE(error) :: err
714      !! Error object with the *status* of the parser
715    err = noerror
716    IF (this%parsed == -1) THEN
717      err = error("argparse: Command-line not parsed (yet)",-19)
718    ELSE IF (this%parsed == 0) THEN
719      err = error("argparse: command-line parsing failed",-20)
720    ELSE IF (.NOT.this%init) THEN
721      err = error("argparse: parser not initialized yet",-1)
722    ENDIF
723    RETURN
724  END FUNCTION ap_check_state
725
726  SUBROUTINE ap_append_arg(this,arg)
727    !! Append an argument to the list of arguments.
728    TYPE(argparser), INTENT(inout) :: this
729      !! An argparser object reference
730    TYPE(argc), INTENT(in)         :: arg
731      !! An [[argparse(module):argc(type)]] object with the argument to add
732    INTEGER                               :: i
733    TYPE(argc), ALLOCATABLE, DIMENSION(:) :: tmp
734    TYPE(error) :: err
735    IF (.NOT.this%init)  THEN
736      err = error("parser not initialized yet",-1) ; RETURN
737    ENDIF
738    ! Empty list : we create it
739    IF (this%nargs == 0) THEN
740      ALLOCATE(this%args(1))
741      this%args(1) = arg
742      this%nargs = 1
743      RETURN
744    ENDIF
745    ! Adds a new argument to the vector of arguments
746    ! we will make a test with move_alloc but i'm not sure it does everything
747    ! the way we want (keep in mind that there is some pointer in argc members
748    ! !!!)
749    ALLOCATE(tmp(this%nargs))
750    DO i=1,this%nargs ; tmp(i) = this%args(i) ; ENDDO
751    CALL clear_argc(this%args)
752    DEALLOCATE(this%args)
753    this%nargs = this%nargs+1 ; ALLOCATE(this%args(this%nargs))
754    DO i=1,this%nargs-1 ; this%args(i) = tmp(i) ; ENDDO
755    CALL clear_argc(tmp)
756    DEALLOCATE(tmp)
757    this%args(i) = arg
758    RETURN
759  END SUBROUTINE ap_append_arg
760
761  FUNCTION ap_get_arg_index(this, name, sflag, lflag)  RESULT(idx)
762    !! Get an argument by name or option flag in the parser.
763    TYPE(argparser), INTENT(in), TARGET    :: this
764      !! An argparser object reference
765    CHARACTER(len=*), INTENT(in), OPTIONAL :: name
766      !! An optional string with the name of the argument
767    CHARACTER(len=*), INTENT(in), OPTIONAL :: lflag
768      !! An optional string with the long option flag of the argument
769    CHARACTER(len=2), INTENT(in), OPTIONAL :: sflag
770      !! An optional string with the short option flag of the argument
771    INTEGER :: idx
772      !! Index of the argument in the internal vector of argument or -1 if no argument is found.
773    INTEGER                       :: i,nn,nl,ns
774    CHARACTER(LEN=:), ALLOCATABLE :: lna, llf
775    CHARACTER(LEN=2)              :: lsf
776    idx = -1
777    IF (.NOT.this%init) RETURN
778    lna="" ; IF(PRESENT(name)) lna = name   ; nn = LEN_TRIM(lna)
779    lsf="" ; IF(PRESENT(sflag)) lsf = sflag ; ns = LEN_TRIM(lsf)
780    llf="" ; IF(PRESENT(lflag)) llf = lflag ; nl = LEN_TRIM(llf)
781    IF (nn == 0 .AND. ns == 0 .AND. nl == 0) RETURN
782    ! empty parser
783    IF (this%nargs == 0) RETURN
784    DO i=1, this%nargs
785      IF ((nn /= 0 .AND. TRIM(this%args(i)%name)  == TRIM(lna)) .OR. &
786          (ns /= 0 .AND. TRIM(this%args(i)%sflag) == TRIM(lsf)) .OR. &
787          (nl /= 0 .AND. TRIM(this%args(i)%lflag) == TRIM(llf))) THEN
788          idx = i ; RETURN
789      ENDIF
790    ENDDO
791    RETURN
792  END FUNCTION ap_get_arg_index
793
794
795  FUNCTION ap_add_option_1(this,dest,sflag,lflag,type,action,default,nrec,help,meta) RESULT(err)
796    !! Add an argument to the parser (interface #1)
797    !!
798    !! The function defines a new argument based on input parameters, checks it and finally sets it
799    !! in the parser. Both **short and long options flags** are mandatory input arguments of the function.
800    !!
801    !!  `type` value should be one of the following module constants (which are aliases from [[string_op(module)]]):
802    !!  - ap_string ([[string_op(module):st_string(variable)]])
803    !!  - ap_complex ([[string_op(module):st_complex(variable)]])
804    !!  - ap_logical ([[string_op(module):st_logical(variable)]])
805    !!  - ap_integer ([[string_op(module):st_integer(variable)]])
806    !!  - ap_real ([[string_op(module):st_real(variable)]])
807    !!
808    !!  `action` value should be one of the following module constants:
809    !!  - [[argparse(module):ap_store(variable)]]
810    !!  - [[argparse(module):ap_append(variable)]]
811    !!  - [[argparse(module):ap_count(variable)]]
812    !!  - [[argparse(module):ap_help(variable)]]
813    !!
814    !!  `nrec` string can take the following forms:
815    !!  tag | description
816    !!  :-: | : -------------
817    !!   ?  | zero or one argument's value
818    !!   *  | any number of arguments
819    !!   +  | one or more argument's value(s)
820    !!   X  | Exactly X values. Where X is the string representation of an integer (0 is accepted).
821    !!
822    !! See also ap_add_option_2 documentation.
823    OBJECT(argparser), INTENT(inout)                     :: this
824      !! An argparser object reference
825    CHARACTER(len=*), INTENT(in)                         :: dest
826      !! A string with the name of the argument
827    CHARACTER(len=2), INTENT(in)                         :: sflag
828      !! A two characters string with the short option flag of the argument
829    CHARACTER(len=*), INTENT(in)                         :: lflag
830      !! A string (3 characters minimum) with the long option flag of the argument
831    INTEGER, INTENT(in), OPTIONAL                        :: type
832      !! An integer with the type of the argument
833    INTEGER, INTENT(in), OPTIONAL                        :: action
834      !! An integer with the action of the argument
835    CHARACTER(len=*), INTENT(in), OPTIONAL               :: default
836      !! A string with the default value of the argument if not provided in the CLI
837    CHARACTER(len=*), INTENT(in), OPTIONAL               :: nrec
838      !! A string with the expected number of specified values for the argument in the CLI.
839    CHARACTER(len=*), INTENT(in), OPTIONAL               :: help
840      !! A string with a short description of the argument
841    CHARACTER(len=*), DIMENSION(:), INTENT(in), OPTIONAL :: meta
842      !! A vector of strings with the displayed value's name(s) of the argument in the help command
843    TYPE(error) :: err
844      !! Error object with the first error encountered in the process.
845    CHARACTER(len=:), ALLOCATABLE :: de,na,he
846    INTEGER                       :: ty,ac
847    TYPE(argc)                    :: arg
848    err = noerror
849    he = ""       ; IF (PRESENT(help))    he = TRIM(help)
850    na = ""       ; IF (PRESENT(nrec))    na = TRIM(nrec)
851    ty = ap_undef ; IF (PRESENT(type))    ty = type
852    ac = ap_undef ; IF (PRESENT(action))  ac = action
853    de =''        ; IF (PRESENT(default)) de = TRIM(default)
854    IF (.NOT.this%init)  THEN
855      err = error("argparse: parser not initialized yet",-1)
856      RETURN
857    ENDIF
858    IF (LEN_TRIM(dest) == 0) THEN
859      err = error("argparse: Invalid argument (empty dest)",-2)
860      RETURN
861    ENDIF
862    arg%name = TRIM(dest) ; arg%help = TRIM(he)
863    IF (PRESENT(meta)) THEN
864      err = ac_check_and_set(arg,sflag,lflag,ty,ac,de,na,meta)
865    ELSE
866      err = ac_check_and_set(arg,sflag,lflag,ty,ac,de,na)
867    ENDIF
868    IF (err /= noerror) RETURN
869    err = ap_check_in_parser(this,arg)
870    IF (err /= noerror) RETURN
871    CALL ap_append_arg(this,arg)
872    CALL clear_argc(arg)
873  END FUNCTION ap_add_option_1
874
875  FUNCTION ap_add_option_2(this,dest,flag,type,action,default,nrec,help,meta) RESULT(err)
876    !! Add an argument to the parser (interface #2)
877    !!
878    !! The function is a wrapper to ap_add_option_1. In this version,
879    !! only one option flag is required. The method only checks for the (trimmed) length of **flag** in
880    !! order to choose wether it is a **short** or **long** option flag. Then the function simply calls
881    !! ap_add_option_1 to set the argument.
882    !!
883    !! Other dummy arguments have the same meaning as in ap_add_option_1.
884    OBJECT(argparser), INTENT(inout)                     :: this
885      !! An argparser object reference
886    CHARACTER(len=*), INTENT(in)                         :: dest
887      !! A string with the name of the argument
888    CHARACTER(len=*), INTENT(in)                         :: flag
889      !! A string with either the short or long option flag
890    INTEGER, INTENT(in), OPTIONAL                        :: type
891      !! A string with the type of the argument
892    INTEGER, INTENT(in), OPTIONAL                        :: action
893      !! A string with the action of the argument
894    CHARACTER(len=*), INTENT(in), OPTIONAL               :: default
895      !! A string with the default value of the argument if not provided in the CLI
896    CHARACTER(len=*), INTENT(in), OPTIONAL               :: nrec
897      !! A string with the expected number of specified values for the argument in the CLI.
898    CHARACTER(len=*), INTENT(in), OPTIONAL               :: help
899      !! A string with a short description of the argument
900    CHARACTER(len=*), DIMENSION(:), INTENT(in), OPTIONAL :: meta
901      !! A vector of strings with the displayed value's name(s) of the argument in the help command
902    TYPE(error) :: err
903      !! Error object with the first error encountered in the process.
904    CHARACTER(len=:), ALLOCATABLE :: sf,lf,de,na,he
905    INTEGER                       :: ty,ac
906    err = noerror
907    sf = '  ' ; lf = ''
908    IF (LEN_TRIM(flag) == 2) THEN
909      sf = TRIM(flag)
910    ELSE
911      lf = TRIM(flag)
912    ENDIF
913    he = ""       ; IF (PRESENT(help))    he = TRIM(help)
914    na = ""       ; IF (PRESENT(nrec))    na = TRIM(nrec)
915    ty = ap_undef ; IF (PRESENT(type))    ty = type
916    ac = ap_undef ; IF (PRESENT(action))  ac = action
917    de = ''       ; IF (PRESENT(default)) de = TRIM(default)
918    ! Calling "true" function
919    IF (PRESENT(meta)) THEN
920      err = ap_add_option_1(this,dest,sf,lf,ty,ac,de,na,he,meta)
921    ELSE
922      err = ap_add_option_1(this,dest,sf,lf,ty,ac,de,na,he)
923    ENDIF
924    RETURN
925  END FUNCTION ap_add_option_2
926
927  FUNCTION ap_check_in_parser(this,arg) RESULT(err)
928    !! Check if an argument is already set in the parser
929    !! An argument is assumed to be already set in the parser if either its name,
930    !! short or long option flag is already defined (in the parser).
931    OBJECT(argparser), INTENT(in) :: this
932      !! An argparser object reference
933    TYPE(argc), INTENT(in)        :: arg
934      !! An argc object to check
935    TYPE(error) :: err
936      !! Error object with -8 id if object is already set, no error otherwise.
937    INTEGER :: i
938    err = noerror
939    IF (this%nargs == 0 ) RETURN
940    DO i=1,this%nargs
941    ! note : we could have use the == operator  but we want to get an specific
942    ! error message)
943      IF (TRIM(this%args(i)%name) == TRIM(arg%name)) THEN
944        err = error("argparse: argument '"//TRIM(arg%name)//"' already defined",-8) ; RETURN
945      ENDIF
946      IF (LEN_TRIM(this%args(i)%sflag) > 0 .AND. &
947          TRIM(this%args(i)%sflag) == TRIM(arg%sflag)) THEN
948        err = error("argparse: flag '"//TRIM(arg%sflag)//"' already defined",-8) ; RETURN
949      ENDIF
950      IF (LEN_TRIM(this%args(i)%lflag) > 0 .AND. &
951          TRIM(this%args(i)%lflag) == TRIM(arg%lflag)) THEN
952        err = error("argparse: flag '"//TRIM(arg%lflag)//"' already defined",-8) ; RETURN
953      ENDIF
954    ENDDO
955    RETURN
956  END FUNCTION ap_check_in_parser
957
958  FUNCTION ap_parse_options(this,cmd,help_req) RESULT(err)
959    !! Parse options of the internal command line
960    !! This (internal) function manages the parsing of the command line options.
961    OBJECT(argparser), INTENT(inout), TARGET :: this
962      !! An argparser object reference
963    TYPE(words), INTENT(inout)               :: cmd
964      !! A [[string_op(module):words(type)]] object with the command-line to parse
965    LOGICAL, INTENT(out)                     :: help_req
966      !! An output logical flag with `.true.` if help option has been found, `.false.` otherwise
967    TYPE(error) :: err
968      !! Error object with the first error encountered in the process
969    CHARACTER(len=1), PARAMETER   :: sq = CHAR(39)
970    CHARACTER(len=:), ALLOCATABLE :: elt
971    INTEGER                       :: arg_idx
972    INTEGER                       :: i,nv,ic
973    err = noerror ; arg_idx = -1
974    help_req = .false.
975    DO WHILE(words_valid(cmd))
976      ! get current element
977      elt = words_current(cmd)
978      ! check element kind: is it an option flag (-1/0)or a value (1)?
979      ic = ap_check_string(this,elt,arg_idx)
980      IF (ic <= 0) THEN
981        IF (arg_idx /= -1) THEN
982          err = ap_fill_argument(this,cmd,this%args(arg_idx))
983          IF (err == 0 .AND. this%args(arg_idx)%paction == ap_help) THEN
984            this%parsed = 1
985            err = argparser_get_value(this,'help',help_req)
986            EXIT
987          ENDIF
988          IF (err /= 0) EXIT
989        ELSE
990          err = error("Unknown argument ('"//elt//"')",-9)
991          EXIT
992        ENDIF
993      ELSE
994        ! We are in the positionals   !!!
995        IF (TRIM(elt) == '--') CALL words_next(cmd)
996        EXIT
997      ENDIF
998      ! iterates to next value
999      CALL words_next(cmd)
1000    ENDDO
1001
1002    ! Do we need to check for error here ?
1003    IF (err /= 0) THEN
1004      this%parsed = 0
1005      arg_idx = -1
1006      RETURN
1007    ELSE IF (help_req) THEN
1008      arg_idx = -1
1009      RETURN
1010    ENDIF
1011
1012    ! Must check here for argument with append action if they have the correct
1013    ! number of argument
1014    DO i=1,this%nargs
1015      nv = words_length(this%args(i)%values)
1016      IF (this%args(i)%fnd                  .AND. &
1017          this%args(i)%paction == ap_append .AND. &
1018          this%args(i)%nrec > 0             .AND. &
1019          nv /= this%args(i)%nrec) THEN
1020        IF (this%args(i)%nrec < nv) THEN
1021          err = ac_fmt_val_err(this%args(i),-18) ! extra values
1022        ELSE
1023          err = ac_fmt_val_err(this%args(i),-17) ! missing values
1024        ENDIF
1025      ENDIF
1026    ENDDO
1027    IF (err /= 0) this%parsed = 0
1028    RETURN
1029  END FUNCTION ap_parse_options
1030
1031  FUNCTION ap_parse_positionals(this,cmd) RESULT(err)
1032    !! Parse positional arguments of the internal command line
1033    !! This (internal) function manages the parsing of the command line positional arguments.
1034    OBJECT(argparser), INTENT(inout) :: this
1035      !! An argparser object reference
1036    TYPE(words), INTENT(inout)       :: cmd
1037      !! A [[string_op(module):words(type)]] object with the command-line to parse
1038    TYPE(error) :: err
1039      !! Error object with the first error encountered in the process
1040    INTEGER                       :: na
1041    CHARACTER(len=:), ALLOCATABLE :: elt
1042    err = noerror
1043    ! cmd iterator is located at the first positional argument
1044
1045    ! no positional required but current word is valid
1046    ! Either : no positional required but valid element is present
1047    !     Or : positional required but no valid element is present
1048    IF ((this%have_posal.AND..NOT.words_valid(cmd)) .OR. &
1049        (.NOT.this%have_posal.AND.words_valid(cmd))) THEN
1050      err = error("Wrong number of arguments",-16) ; RETURN
1051    ENDIF
1052    ! ugly patch : we must clear this%posals%values because of the automatic
1053    ! setting of default value
1054    CALL words_clear(this%posals%values)
1055    this%posals%fnd = .true.
1056    DO
1057      na = words_length(this%posals%values)
1058      IF (words_valid(cmd)) THEN
1059        ! Gets the element value
1060        elt = words_current(cmd)
1061        ! and add it
1062        CALL words_append(this%posals%values,elt)
1063      ELSE
1064        ! no more elements: check against the number of expected records
1065        ! 1 or + elements expected but nothing has been saved
1066        IF (this%posals%nrec == -3 .AND. na > 1) THEN
1067          err = error("Extra value(s) found (positionals arguments)",-18)
1068        ELSE IF (this%posals%nrec == -2 .AND. na == 0) THEN
1069          err = error("Missing values (positionals arguments)",-17)
1070        ELSE IF (this%posals%nrec > 0 .AND. na /= this%posals%nrec) THEN
1071          IF (na > this%posals%nrec) THEN
1072            err = error("Extra value(s) found (positionals arguments)",-18)
1073          ELSE
1074            err = error("Missing values (positionals arguments)",-17)
1075          ENDIF
1076        ENDIF
1077        EXIT
1078      ENDIF
1079      ! get to the next element
1080      CALL words_next(cmd)
1081    ENDDO
1082    IF (err /= noerror) THEN
1083      this%posals%fnd = .false.
1084      this%parsed = 0
1085    ENDIF
1086    RETURN
1087  END FUNCTION ap_parse_positionals
1088
1089  FUNCTION ap_fill_argument(this,cmd,arg) RESULT(err)
1090    !! Fill an argument with values
1091    !!
1092    !! The function parses remaining parts of the command line from the position of
1093    !! the given argument and attempts to retrieve its value(s) (if any).
1094    !! Several tests are performed and may raise errors. The function always stops
1095    !! at the first error encountered which can be one of the following :
1096    !! - Invalid value type (conversion check failed)
1097    !! - Missing values (can not get as much values as defined in the argument)
1098    !! - Extra values found (more values can be retrieved from the command line
1099    !!   than defined in the argument)
1100    OBJECT(argparser), INTENT(inout)  :: this
1101      !! An argparser object reference
1102    TYPE(words), INTENT(inout)        :: cmd
1103      !! The command line
1104    TYPE(argc), INTENT(inout), TARGET :: arg
1105      !! An argc object reference with the argument currently processed.
1106    TYPE(error) :: err
1107      !! Error object with the first error encountered in the process
1108    INTEGER                       :: ca, isopt, itmp
1109    LOGICAL                       :: ltmp
1110    CHARACTER(len=:), ALLOCATABLE :: elt
1111    err = noerror
1112    ! We always reset arguments value if we are in store mode.
1113    ! If one wants to set an option several times and keeps track of the
1114    ! previous values, she must use 'append'
1115    IF (arg%paction == ap_store) CALL words_clear(arg%values)
1116    ! Gets values as a function of the expected number of records
1117    IF (arg%nrec == 0) THEN
1118      ! argparser_parse (main parsing method) reset all values: for 0 nrec
1119      ! we should have at least one value saved which is the default.
1120      ! if it is not the case we set default as values of the argument
1121      IF (words_length(arg%values) == 0) CALL words_append(arg%values,arg%default)
1122      ! NOW HANDLING 0 records case:
1123      ! we do not have to consume any argument but :
1124      !  - trigger a boolean (set it to .not.default)
1125      !  - increase a counter (if action == 'count')
1126      IF (arg%paction == ap_count) THEN
1127        elt = words_pop(arg%values)
1128        READ(elt,*) itmp ; itmp = itmp + 1
1129        CALL words_append(arg%values,TO_STRING(itmp))
1130      ELSE IF (arg%ptype == ap_logical) THEN
1131        elt = words_pop(arg%values)
1132        READ(elt,*) ltmp
1133        CALL words_append(arg%values,TO_STRING(.NOT.ltmp))
1134      ENDIF
1135    ELSE
1136      ! For any other case, the algorithm is quite simple :
1137      ! We consume tokens of the command-line until either the end or
1138      ! the next option (or '--' separator)
1139      ! When the exit condition is met we perform some tests based on the
1140      ! expected argument and sets the returned error object...
1141      ca = 0 ; IF(arg%paction == ap_append) ca = words_length(arg%values)
1142      DO
1143        CALL words_next(cmd) ; elt = words_current(cmd) ; isopt = ap_check_string(this,elt)
1144        ! We have a "valid" value
1145        IF (((.NOT.words_valid(cmd)).EQV.(isopt<=0)).AND.TRIM(elt) /= '--') THEN
1146          ! we have a value that we should check for conversion !
1147          err = ac_check_value(arg,elt)
1148          IF (err /= 0) THEN
1149            err = ac_fmt_val_err(arg,-2)
1150          ELSE
1151            CALL words_append(arg%values,elt) ; ca = ca + 1
1152          ENDIF
1153        ELSE
1154          ! 3 cases are possible :
1155          !    1) we have consumed all argument of command line
1156          !    2) current argument is not a value !
1157          !    3) current argument the separator '--'
1158          IF (isopt <= 0 .OR. TRIM(elt)=='--') CALL words_previous(cmd)
1159          IF (arg%nrec == -2 .AND. words_length(arg%values) == 0) &
1160            err = ac_fmt_val_err(arg,-17)
1161          IF (arg%paction /= ap_append .AND. arg%nrec > 0 .AND. ca /= arg%nrec) &
1162          THEN
1163            IF (ca > arg%nrec) THEN
1164              err = ac_fmt_val_err(arg,-18)
1165            ELSE
1166              err = ac_fmt_val_err(arg,-17)
1167            ENDIF
1168          ENDIF
1169          EXIT
1170        ENDIF
1171        IF (err /= noerror) EXIT
1172        IF (arg%nrec == -3) EXIT
1173        IF (ca == arg%nrec) EXIT
1174      ENDDO
1175    ENDIF
1176    arg%fnd = (err == noerror)
1177    RETURN
1178  END FUNCTION ap_fill_argument
1179
1180  FUNCTION ap_split_cmd(this,string,new_cmd,rhelp) RESULT(err)
1181    !! Preprocess the command line
1182    !! The function reads and splits the given string so merged options/values
1183    !! are splitted and saves the resulting string elements in a list of words.
1184    !! @warning
1185    !! For compilers that does not support allocatable strings in derived types,
1186    !! computation are highly dependent of [[string_op(module):st_slen(variable):
1187    !! tokens length are limited by this parameter.
1188    IMPLICIT NONE
1189    OBJECT(argparser), INTENT(in) :: this
1190      !! An argparser object reference
1191    CHARACTER(len=*), INTENT(in)  :: string
1192      !! A string to process
1193    TYPE(words), INTENT(out)      :: new_cmd
1194      !! An output [[string_op(module):words(type)]] object with the processed command line
1195    LOGICAL, INTENT(out)          :: rhelp   
1196      !! An output boolean flag with `.true.` if help is requested, `.false.` otherwise
1197    TYPE(error) :: err
1198      !! Error object with the first error encountered in the process
1199    INTEGER                       :: isopt,j,tl,res
1200    CHARACTER(len=:), ALLOCATABLE :: elt
1201    TYPE(words)                   :: splitted
1202    INTEGER                       :: arg_idx
1203    err = noerror ; rhelp = .false.
1204    IF (LEN_TRIM(string) == 0) THEN
1205      err = error('internal error (empty string)',-255)
1206      RETURN
1207    ENDIF
1208    ! split input command line in words !
1209    call words_extend(splitted,string," ",.true.)
1210    ! reset iterator
1211    CALL words_reset(splitted)
1212    DO WHILE(words_valid(splitted))
1213      elt = words_current(splitted) ; tl = LEN_TRIM(elt)
1214      isopt = ap_check_string(this,TRIM(elt),arg_idx)
1215      ! we have a short option : maybe we need to split it
1216      IF (isopt == -1 ) THEN
1217        DO j=2,tl
1218          res = ap_check_string(this,"-"//elt(j:j),arg_idx)
1219          ! great we have another short option flag
1220          IF (res == -1 .AND. arg_idx /= -1) THEN ! another short option !
1221            rhelp = (this%args(arg_idx)%paction == ap_help.OR.rhelp)
1222            ! we must not set some argument's values here  for help argument
1223            ! if auto is not set the parse method will disable the option
1224            ! during next! parsing process
1225            CALL words_append(new_cmd,"-"//elt(j:j))
1226          ELSE
1227            IF (j == 2) THEN ! no more option flag !
1228              CALL words_append(new_cmd,TRIM(elt(j-1:)))
1229            ELSE
1230              CALL words_append(new_cmd,TRIM(elt(j:)))
1231            ENDIF
1232            EXIT ! WE MUST EXIT !!!!!!!
1233          ENDIF
1234        ENDDO
1235      ELSE
1236        IF (isopt == 0.AND.arg_idx /= -1) &
1237        rhelp = (this%args(arg_idx)%paction == ap_help.OR.rhelp)
1238        ! we must not set some argument's values here for help argument
1239        ! if auto is not set the parse method will disable the option during
1240        ! next parsing process
1241        CALL words_append(new_cmd,TRIM(elt))
1242      ENDIF
1243      ! Iterates to next word
1244      CALL words_next(splitted)
1245    ENDDO
1246    CALL words_clear(splitted)
1247    RETURN
1248  END FUNCTION ap_split_cmd
1249   
1250  FUNCTION ap_check_string(this,string,idx) RESULT(ret)
1251    !! Check if a string is an option flag
1252    !! The function checks if the given string is either a short, long option flag or a value.
1253    !! @warning
1254    !! An empty string is considered as a value !
1255    OBJECT(argparser), INTENT(in)              :: this
1256      !! An argparser object reference
1257    CHARACTER(len=*), INTENT(in)               :: string
1258      !! A string to check
1259    INTEGER, INTENT(out), OPTIONAL             :: idx
1260      !! An optional output intger with the index of the afferent argument in the parser (-1 if not found)
1261    INTEGER :: ret
1262      !! Return code with the following possible values:
1263      !! - -1 if the string is a SHORT option flag
1264      !! - 0 if the string is a LONG option flag
1265      !! - 1 if it considered as a value
1266    CHARACTER(len=52), PARAMETER :: alpha = "abcdefghijklmnopqrstuvwxyz&
1267                                            &ABCDEFGHIJKLMNOPQRSTUVWXYZ"
1268    ! return code can be either :
1269    !  -1 : it's a short option flag
1270    !   0 : it's a long option flag
1271    !   1 : it's a value
1272    ! The combination of the (optional) output index and the return code
1273    ! allows to check if an option is known or not
1274    ret = 1
1275    ! '--' is special : it is a separator that is seen as a value.
1276    IF (TRIM(string) == '--') RETURN
1277    IF (PRESENT(idx)) idx = -1
1278    ! First we will check the two first characters of the string
1279    IF (LEN_TRIM(string) >= 2) THEN
1280      IF (string(1:1) == ACHAR(45)) THEN
1281        ! It's a long option flag !
1282        IF (string(2:2) == ACHAR(45)) THEN
1283          ret = 0
1284          IF (PRESENT(idx)) idx = ap_get_arg_index(this,lflag=TRIM(string))
1285        ELSE
1286          ! It's a short option flag !
1287          IF (INDEX(alpha, string(2:2)) /= 0) THEN
1288            ret = -1
1289            IF (PRESENT(idx)) idx = ap_get_arg_index(this,sflag=string(1:2))
1290          ENDIF
1291        ENDIF
1292      ENDIF
1293    ENDIF
1294    RETURN
1295  END FUNCTION ap_check_string
1296
1297  FUNCTION ap_gen_help(this) RESULT(hlp)
1298    !! Generate the help string
1299    OBJECT(argparser), INTENT(inout) :: this
1300      !! An argparser object reference
1301    CHARACTER(len=:), ALLOCATABLE :: hlp
1302      !! The formatted help message
1303    CHARACTER(len=:), ALLOCATABLE :: copt,spc,opts,text
1304    INTEGER                       :: i,j,ia,optmw,i1,io,n,zw,zh
1305    IF (this%width == 0) CALL fs_termsize(zh,this%width)
1306    zw = this%width
1307    ! Sets usage
1308    CALL ap_format_usage(this,optmw)
1309    ! computes the help position
1310    optmw = optmw +2 + 2 ! +2 for indentation + 2 for spaces after option
1311    optmw = MIN(MAX(5,this%mxhlpos-1),optmw)
1312    hlp = TRIM(this%usg)//NEW_LINE('A')//NEW_LINE('A')
1313    ! Sets description
1314    IF (LEN_TRIM(this%descr) /= 0) &
1315      hlp=hlp//getpar(this%descr,zw,2)//NEW_LINE('A')//NEW_LINE('A')
1316    ! Sets positionals
1317    IF (this%have_posal) THEN
1318      IF (LEN_TRIM(this%posals%help) /= 0) THEN
1319        hlp=hlp//'positionals:'//NEW_LINE('A')
1320        copt = ac_get_opt_str(this%posals) ; n = LEN_TRIM(copt)
1321        hlp=hlp//getpar(copt,zw,idt1=2)
1322        ! we must put help on a new line : no need to extends opt with spaces
1323        IF (n > optmw-2) THEN
1324          hlp=hlp//NEW_LINE('A')//REPEAT(CHAR(32),optmw)
1325        ELSE
1326          hlp=hlp//REPEAT(CHAR(32),optmw-n-2)
1327        ENDIF
1328        spc = REPEAT(CHAR(32),optmw)
1329        text = getpar(this%posals%help,zw-optmw,0,0)
1330        j=1
1331        DO WHILE(j <= LEN(text))
1332          i = INDEX(text(j:),NEW_LINE('A'))
1333          IF (i /= 0) THEN
1334            hlp=hlp//text(j:j+i-1)//spc
1335            j=j+i
1336          ELSE
1337            hlp=hlp//text(j:) ; EXIT
1338          ENDIF
1339        ENDDO
1340        hlp=hlp//NEW_LINE('A')//NEW_LINE('A')
1341      ENDIF
1342    ENDIF
1343    ! Sets options
1344    IF (this%nargs > 0) THEN
1345      opts=''
1346      DO ia=1, this%nargs
1347        IF (LEN_TRIM(this%args(ia)%help) /= 0) THEN
1348          copt = ac_get_opt_str(this%args(ia)) ; n = LEN_TRIM(copt)
1349          opts=opts//getpar(copt,zw,idt1=2)
1350          ! we must put help on a new line : no need to extends opt with spaces
1351          IF (n > optmw-2) THEN
1352            opts=opts//NEW_LINE('A')//REPEAT(CHAR(32),optmw)
1353          ELSE
1354            opts=opts//REPEAT(CHAR(32),optmw-n-2)
1355          ENDIF
1356          spc = REPEAT(CHAR(32),optmw)
1357          text = getpar(this%args(ia)%help,zw-optmw,0,0)
1358          j=1
1359          DO WHILE(j <= LEN(text))
1360            i = INDEX(text(j:),NEW_LINE('A'))
1361            IF (i /= 0) THEN
1362              opts=opts//text(j:j+i-1)//spc
1363              j=j+i
1364            ELSE
1365              opts=opts//text(j:) ; EXIT
1366            ENDIF
1367          ENDDO
1368          opts=opts//NEW_LINE('A')
1369        ENDIF
1370      ENDDO
1371      IF (LEN_TRIM(opts) > 0) hlp=hlp//'options:'//NEW_LINE('A')//opts
1372    ENDIF
1373    IF (LEN_TRIM(this%eplg) /= 0) THEN
1374      hlp=hlp//NEW_LINE('A')//getpar(this%eplg,zw,2)//NEW_LINE('A')
1375    ENDIF
1376    RETURN
1377  END FUNCTION ap_gen_help
1378
1379  SUBROUTINE ap_format_usage(this,optmw)
1380    !! Format command line usage.
1381    !!
1382    !! The subroutine creates and formats the command line usage of the
1383    !! given argparser object. If [[argparser(type):usg(variable)]] is already set (i.e. not empty)
1384    !! then the method only computes the maximum width of the option part of the usage command
1385    !! (see `optmw` argument description) if needed. In the other case, the method builds the usage
1386    !! line based on the arguments stored in the parser.
1387    OBJECT(argparser), INTENT(inout) :: this
1388      !! An argparser object reference
1389    INTEGER, INTENT(out), OPTIONAL   :: optmw
1390      !! An optional integer with the maximum length of the option part of the usage command.
1391      !! This variable is intended to set a fancy indentation while printing option in the helper.
1392    CHARACTER(len=:), ALLOCATABLE :: usage, idts, copt,pgn
1393    INTEGER                       :: i,omw,idt,cl,wopt
1394    ! Get/Checks/Sets maximum width
1395    ! get program name
1396    pgn = get_progname()
1397    omw = 0
1398    IF (LEN_TRIM(this%usg) == 0) THEN
1399      idt = 8 + LEN_TRIM(pgn)
1400      ALLOCATE(CHARACTER(LEN=idt+1) :: idts)
1401      idts(1:1) = NEW_LINE('A') ; idts(2:idt+1) = CHAR(32)
1402      ! Builds the usage string
1403      usage = "usage: "//TRIM(pgn)//CHAR(32)
1404      ! Looping over arguments
1405      cl = idt
1406      DO i=1,this%nargs
1407        ! gets max length for help options
1408        copt = ac_get_opt_str(this%args(i)) ; wopt=LEN_TRIM(copt)
1409        IF (LEN_TRIM(this%args(i)%help) /= 0.AND. wopt > omw) omw = wopt
1410        !IF (LEN_TRIM(copt) > omw) omw = LEN_TRIM(copt) ; copt=""
1411        ! Retrieve current argument usage string
1412        copt = ac_get_usg_opt_str(this%args(i))
1413        ! Set a new line if it does not hold width
1414        IF (cl+LEN_TRIM(copt) > this%width) THEN
1415          cl = idt ; usage = usage(:)//idts(:)
1416        ENDIF
1417        ! Write the argument usage + a blank space !
1418        usage = usage(:)//TRIM(copt)//CHAR(32)
1419        cl = cl + LEN_TRIM(copt)+1
1420      ENDDO
1421      IF (PRESENT(optmw)) optmw = omw
1422      ! handling positional
1423      IF (this%have_posal) THEN
1424        copt = ac_get_usg_opt_str(this%posals)
1425        IF (LEN_TRIM(copt) > 0) THEN
1426          ! print newline if it cannot fit
1427          IF (cl+LEN_TRIM(copt) > this%width) usage = usage(:)//idts(:)
1428          usage = usage(:)//TRIM(copt)
1429        ENDIF
1430      ENDIF
1431      this%usg = usage
1432    ELSE
1433      IF (PRESENT(optmw)) THEN
1434        DO i=1,this%nargs
1435          copt = ac_get_opt_str(this%args(i)) ; wopt=LEN_TRIM(copt)
1436          IF (LEN_TRIM(this%args(i)%help) /= 0.AND.wopt > omw) omw = wopt
1437          copt = ""
1438        ENDDO
1439        optmw = omw
1440      ENDIF
1441    ENDIF
1442  END SUBROUTINE ap_format_usage
1443
1444  SUBROUTINE ap_affect_parser(this,other)
1445    !! Argparser assignment operator subroutine
1446    !! The subroutine assigns `other` to `this`
1447    TYPE(argparser), INTENT(out) :: this
1448      !! An argparser object to be assigned
1449    TYPE(argparser), INTENT(in)  :: other
1450      !! An argparser object to assign
1451    INTEGER :: i
1452    IF (other%nargs > 0) THEN
1453      this%nargs = other%nargs
1454      ALLOCATE(this%args(this%nargs))
1455      DO i=1,this%nargs ; this%args(i) = other%args(i) ; ENDDO
1456    ENDIF
1457    this%have_posal = other%have_posal
1458    this%posals     = other%posals
1459    this%parsed     = other%parsed
1460#if HAVE_FTNDTSTR
1461    IF (ALLOCATED(other%usg))   this%usg   = other%usg
1462    IF (ALLOCATED(other%descr)) this%descr = other%descr
1463    IF (ALLOCATED(other%eplg))  this%eplg  = other%eplg
1464#else
1465    this%usg   = other%usg
1466    this%descr = other%descr
1467    this%eplg  = other%eplg
1468#endif
1469    this%mxhlpos = other%mxhlpos
1470    this%width   = other%width
1471    this%init    = other%init
1472  END SUBROUTINE ap_affect_parser
1473
1474  ! argc methods
1475  ! ------------
1476
1477  SUBROUTINE ac_affect_arg(this,other)
1478    !! Argc object assignment operator subroutine
1479    !! The subroutine assigns `other` to `this`
1480    TYPE(argc), INTENT(out) :: this
1481      !! An argc object to be assigned
1482    TYPE(argc), INTENT(in)  :: other
1483      !! An argc object to assign
1484    this%nrec   = other%nrec
1485    this%paction = other%paction
1486    this%ptype   = other%ptype
1487    this%fnd  = other%fnd
1488    this%sflag  = other%sflag
1489#if HAVE_FTNDTSTR
1490    IF (ALLOCATED(other%name))    this%name    = other%name
1491    IF (ALLOCATED(other%lflag))   this%lflag   = other%lflag
1492    IF (ALLOCATED(other%help))    this%help    = other%help
1493    IF (ALLOCATED(other%default)) this%default = other%default
1494#else
1495    this%name    = other%name
1496    this%lflag   = other%lflag
1497    this%default = other%default
1498    this%help    = other%help
1499#endif
1500    CALL words_clear(this%values)
1501    CALL words_clear(this%meta)
1502    this%values = other%values
1503    this%meta   = other%meta
1504    RETURN
1505  END SUBROUTINE ac_affect_arg
1506
1507  FUNCTION ac_equals_arg(this,other) RESULT(ret)
1508    !! Check if two arguments are identical
1509    !! The method checks if two arguments are equal based on their name, short option flag and long
1510    !! option flag.Two arguments are considered equals if at least one of these three members is equal
1511    !! and not empty.
1512    TYPE(argc), INTENT(in) :: this
1513      !! First argc object to compare
1514    TYPE(argc), INTENT(in) :: other
1515      !! Second argc object to compare
1516    LOGICAL :: ret
1517      !! `.true.` if the two objects are equal, `.false.` otherwise.
1518    CHARACTER(len=:), ALLOCATABLE :: tna,ona,tsf,osf,tlf,olf
1519    INTEGER                       :: tn,ts,tl,on,os,ol
1520    ret = .false.
1521    tsf = TRIM(this%sflag) ; osf = TRIM(this%sflag)
1522#if HAVE_FTNDTSTR
1523    tna="" ; IF (ALLOCATED(this%name))   tna=TRIM(this%name)
1524    ona="" ; IF (ALLOCATED(other%name))  ona=TRIM(other%name)
1525    tlf="" ; IF (ALLOCATED(this%lflag))  tlf=TRIM(this%lflag)
1526    olf="" ; IF (ALLOCATED(other%lflag)) olf=TRIM(other%lflag)
1527#else
1528    tna=TRIM(this%name)  ; ona=TRIM(other%name)
1529    tlf=TRIM(this%lflag) ; olf=TRIM(other%lflag)
1530#endif
1531    tn=LEN_TRIM(tna) ; on=LEN_TRIM(ona)
1532    tl=LEN_TRIM(tlf) ; ol=LEN_TRIM(olf)
1533    ts=LEN_TRIM(tsf) ; os=LEN_TRIM(osf)
1534    ! check on name :
1535    ! Returns True if at least of name, sflag and lflag is set to non-empty
1536    ! string and is indentical for the two argument !
1537    ret = ((tn/=0 .AND. on==tn) .AND. tna == ona) .OR. &
1538          ((tl/=0 .AND. ol==tl) .AND. tlf == olf) .OR. &
1539          ((ts/=0 .AND. os==ol) .AND. tsf == osf)
1540    DEALLOCATE(tna,ona,tsf,osf,tlf,olf)
1541  END FUNCTION ac_equals_arg
1542
1543  FUNCTION ac_differs_arg(this,other) RESULT(ret)
1544    !! Check if two arguments are different
1545    !! The method checks if two arguments are different based on their names, short option flag
1546    !! and long option flag.
1547    !! @note
1548    !! This function is the extact contrary of [[argparse(module):ac_equals_arg(function)]] !
1549    TYPE(argc), INTENT(in) :: this
1550      !! First argc object to compare
1551    TYPE(argc), INTENT(in) :: other
1552      !! Second argc object to compare
1553    LOGICAL :: ret
1554      !! `.true.` if the two objects are different, `.false.` otherwise.
1555    ret = .NOT. ac_equals_arg(this,other)
1556  END FUNCTION ac_differs_arg
1557
1558  SUBROUTINE ac_clear_arg_sc(arg)
1559    !! argc destructor (scalar)
1560    !! The subroutine frees all memory used by an argc object and resets its member to
1561    !! default values.
1562    TYPE(argc), INTENT(inout) :: arg
1563      !! An argc object to free
1564    CALL words_clear(arg%values)
1565    CALL words_clear(arg%meta)
1566    arg%ptype   = ap_logical
1567    arg%paction = ap_store
1568    arg%nrec    = 0
1569    arg%fnd     = .false.
1570    arg%sflag   = "  "
1571#if HAVE_FTNDTSTR
1572    IF (ALLOCATED(arg%default)) DEALLOCATE(arg%default)
1573    IF (ALLOCATED(arg%name))    DEALLOCATE(arg%name)
1574    IF (ALLOCATED(arg%lflag))   DEALLOCATE(arg%lflag)
1575    IF (ALLOCATED(arg%help))    DEALLOCATE(arg%help)
1576#else
1577    arg%default = ""
1578    arg%name    = ""
1579    arg%help    = ""
1580    arg%lflag   = ""
1581#endif
1582  END SUBROUTINE ac_clear_arg_sc
1583
1584  SUBROUTINE ac_clear_arg_ve(args)
1585    !! argc destructor (vector)
1586    TYPE(argc), INTENT(inout), DIMENSION(:), TARGET :: args
1587      !! A vector of argc objects to free
1588    INTEGER :: i
1589    CALL words_clear(args%values)
1590    CALL words_clear(args%meta)
1591    DO i=1, SIZE(args)
1592      args(i)%ptype   = ap_logical
1593      args(i)%paction = ap_store
1594      args(i)%nrec    = 0
1595      args(i)%fnd     = .false.
1596      args(i)%sflag    = "  "
1597#if HAVE_FTNDTSTR
1598      IF (ALLOCATED(args(i)%default)) DEALLOCATE(args(i)%default)
1599      IF (ALLOCATED(args(i)%name))    DEALLOCATE(args(i)%name)
1600      IF (ALLOCATED(args(i)%lflag))   DEALLOCATE(args(i)%lflag)
1601      IF (ALLOCATED(args(i)%help))    DEALLOCATE(args(i)%help)
1602#else
1603      args(i)%default = ""
1604      args(i)%name    = ""
1605      args(i)%help    = ""
1606      args(i)%lflag   = ""
1607#endif
1608    ENDDO
1609  END SUBROUTINE ac_clear_arg_ve
1610
1611  FUNCTION ac_found(this) RESULT(yes)
1612    !! Check if argument has been found in the command line
1613    TYPE(argc), INTENT(in) :: this
1614      !! An argc object
1615    LOGICAL :: yes
1616      !! `.true.` if the option has been parsed, `.false.` otherwise
1617    yes = this%fnd
1618  END FUNCTION ac_found
1619
1620  FUNCTION ac_get_num_values(this) RESULT(num)
1621    !! Get the actual number of values stored in the argument
1622    TYPE(argc), INTENT(in) :: this
1623      !! An argc object
1624    INTEGER :: num
1625      !! The number of values stored in the argument
1626    num = words_length(this%values)
1627  END FUNCTION ac_get_num_values
1628
1629  FUNCTION ac_get_usg_opt_str(arg) RESULT(line)
1630    !! Build and format the option string for the usage part of the help message
1631    !! The function is private part of the help builder. It creates the
1632    !! option string part of a given argument.
1633    TYPE(argc), INTENT(in), TARGET :: arg
1634      !! An argc object
1635    CHARACTER(len=:), ALLOCATABLE :: line,meta
1636      !! Allocated string with the option flags string
1637    line=""
1638    IF (LEN_TRIM(arg%sflag) > 0) THEN
1639      line="["//TRIM(arg%sflag)
1640    ELSE IF (LEN_TRIM(arg%lflag) > 0) THEN
1641      line="["//TRIM(arg%lflag)
1642    ENDIF
1643    meta = TRIM(words_get(arg%meta,1))
1644    SELECT CASE (arg%nrec)
1645      CASE (-3)
1646        line=line(:)//" ["//meta//"]"
1647      CASE (-2)
1648        line=line(:)//CHAR(32)//meta//" [...]"
1649      CASE (-1)
1650        line=line(:)//" ["//meta//" [...]]"
1651      CASE (0)
1652        ! DO NOTHING BUT MUST BE EXPLICITELY SET
1653      CASE DEFAULT
1654        meta = words_to_string(arg%meta," ")
1655        line = line(:)//CHAR(32)//meta
1656    END SELECT
1657    IF (line(1:1) == "[") line=line(:)//"]"
1658    RETURN
1659  END FUNCTION ac_get_usg_opt_str
1660
1661  FUNCTION ac_get_opt_str(arg) RESULT(line)
1662    !! Build and format the option flag string for the option part of the help message
1663    !! The function is private part of the help builder. It creates the
1664    !! option string part of a given argument for the options part of the help.
1665    TYPE(argc), INTENT(in), TARGET :: arg
1666      !! An argc object
1667    CHARACTER(len=:), ALLOCATABLE :: line
1668      !! Allocated string with the option flags string
1669    CHARACTER(len=:), ALLOCATABLE :: values,m
1670    ! creates values string
1671    m = TRIM(words_get(arg%meta,1))
1672    SELECT CASE (arg%nrec)
1673      CASE(-3)
1674        values="["//m//"]"
1675      CASE(-2)
1676        values=m//" [...]"
1677      CASE(-1)
1678        values="["//m//" [...]]"
1679      CASE (0)
1680        values=""
1681      CASE DEFAULT
1682        values = words_to_string(arg%meta," ")
1683     END SELECT
1684     ! build the final string
1685     ! -s values, --long values
1686     line=""
1687     IF (LEN_TRIM(arg%sflag) > 0) THEN
1688       line=TRIM(arg%sflag)//CHAR(32)//TRIM(values)
1689       IF (LEN_TRIM(arg%lflag) > 0) line = line(:)//", "
1690     ENDIF
1691     IF (LEN_TRIM(arg%lflag) > 0) THEN
1692         line = line(:)//TRIM(arg%lflag)//CHAR(32)//TRIM(values)
1693     ENDIF
1694     ! this line handles positionals :)
1695     IF (arg%name == 'positional') line = TRIM(values)
1696    RETURN
1697  END FUNCTION ac_get_opt_str
1698
1699  FUNCTION ac_fmt_val_err(arg,id) RESULT(ret)
1700    !! Format specific error for argc values
1701    !! The function formats argparse specific errors when extra (missing) values
1702    !! are (not) set or when given values are not consistent with argument's type.
1703    !! For each of these errors, the basic error is updated with a more precise
1704    !! message.
1705    TYPE(argc), INTENT(in) :: arg
1706      !! An argc object
1707    INTEGER, INTENT(in)    :: id
1708      !! Integer with the error id (-3, -15 or -16 in fact)
1709    TYPE(error) :: ret
1710      !! Error object with the updated error message.
1711    CHARACTER(len=:), ALLOCATABLE :: msg,nv
1712    IF (LEN_TRIM(arg%sflag) /= 0) THEN
1713      msg=' ('//arg%sflag
1714    ELSE ! note that normally if no sflag are present lflag should be set
1715      msg=' ('//TRIM(arg%lflag)
1716    ENDIF
1717    nv = to_string(arg%nrec) ; IF (arg%nrec < 0) nv='1'
1718    ! we only handle ids : -2 (invalid arg), -17 (missing values), -18 (extra values)
1719    SELECT CASE(id)
1720      CASE (-2)  ! invalid value: cannot cast ->
1721        msg = msg//" option expects '"//apt2str(arg%ptype)//"' values)"
1722      CASE (-17) ! missing values -> -17
1723        IF (arg%nrec == -2) THEN
1724          msg = msg//' takes at least '//nv//' value(s))'
1725        ELSE
1726          msg = msg//' takes exactly '//nv//' value(s))'
1727        ENDIF
1728      CASE (-18) ! extra values -> -18
1729        IF (arg%nrec == -3) THEN
1730          msg = msg//' takes at most '//nv//' value(s))'
1731        ELSE
1732          msg = msg//' takes exactly '//nv//' value(s))'
1733        ENDIF
1734      CASE DEFAULT
1735        msg=''
1736    END SELECT
1737    ret = error(msg,id)
1738  END FUNCTION ac_fmt_val_err
1739
1740  FUNCTION ac_check_and_set(this,sf,lf,ty,ac,de,na,meta,check_flag) RESULT(ret)
1741    !! Interface to all argc's member tests
1742    !! The function calls all the tests to perform on argc members. Some of these tests can
1743    !! alter argc's member values to fit argparser's requirements.
1744    !!
1745    !! On success, `noerror` is returned. Otherwise -9 error code is returned. Errors are only
1746    !! produced by misuse of the function arguments. In such case, the program should be
1747    !! stopped: note that such ezrror should not occur in _released_ programs.
1748    TYPE(argc), INTENT(inout)                            :: this
1749      !! An argc object
1750    CHARACTER(len=2), INTENT(in)                         :: sf
1751      !! A string (2 chars wide) with the short option flag
1752    CHARACTER(len=*), INTENT(in)                         :: lf
1753      !! A string with the long option flag
1754    INTEGER, INTENT(in)                                  :: ty
1755      !! An integer with the type of the argument
1756    INTEGER, INTENT(in)                                  :: ac
1757      !! An integer with the action of the argument
1758    CHARACTER(len=*), INTENT(in)                         :: de
1759      !! A string with the default value of the argument
1760    CHARACTER(len=*), INTENT(in)                         :: na
1761      !! A string pattern with the expected number of values for the argument
1762    CHARACTER(len=*), INTENT(in), DIMENSION(:), OPTIONAL :: meta
1763      !! An optional vector of strings with the Meta-name of the values
1764    LOGICAL, INTENT(in), OPTIONAL                        :: check_flag
1765      !! An optional boolean flag hat instructs the method wether to check for option flag
1766      !! or not. By default this test is enabled but it should be disabled if one wants to
1767      !! check for POSITIONAL arguments as they do not have option flags.
1768    TYPE(error) :: ret
1769      !! Error object with the first error encountered in the process
1770    LOGICAL :: zflag
1771    zflag = .true. ; IF (PRESENT(check_flag)) zflag = check_flag
1772    ! 1) CHECKING FLAG SYNTAX
1773    IF (zflag) THEN
1774      ret = ac_check_flags(this,sf,lf) ; IF (ret /= 0) RETURN
1775    ELSE
1776      this%sflag = sf ; this%lflag = lf
1777    ENDIF
1778    ! 2) CHECKING AND SETTING action, type, default value and number of record
1779    ret = ac_check_ac_ty_de_na(this,ac,ty,de,na) ; IF (ret /= 0) RETURN
1780    ! 3) Sets/updates meta name
1781    IF (PRESENT(meta)) THEN
1782      CALL ac_set_meta(this,meta)
1783    ELSE
1784      CALL ac_set_meta(this)
1785    ENDIF
1786    RETURN
1787  END FUNCTION ac_check_and_set
1788
1789  FUNCTION ac_check_ac_ty_de_na(this,ac,ty,de,na) RESULT(ret)
1790    !! Check and set argc's action, type and default value
1791    !! The method checks if input argument's options are valid and update the argc object
1792    !! consequently.
1793    !!
1794    !! On success, `noerror` is returned. Otherwise -9 error code is returned. Errors are only
1795    !! produced by misuse of the function arguments.
1796    TYPE(argc), INTENT(inout)  :: this
1797      !! An argc object to update
1798    INTEGER, INTENT(in)          :: ac
1799      !! An integer with the action to set and check
1800    INTEGER, INTENT(in)          :: ty
1801      !! An integer with the type to set and check
1802    CHARACTER(len=*), INTENT(in) :: de
1803      !! A string with the default value to set and check
1804    CHARACTER(len=*), INTENT(in) :: na
1805      !! A string with the expected number of value to set and check
1806    TYPE(error) :: ret
1807      !! Error object with the first error encountered in the process
1808    CHARACTER(len=:), ALLOCATABLE :: eprf,zna
1809    TYPE(error)                   :: uty,ina
1810    ret = noerror
1811    eprf = 'argparse: '//"Invalid argument `"//TRIM(this%name)//"'"
1812    uty = error(eprf//" (type)",-9)
1813    ina = error(eprf//" (inconsistent nargs)",-9)
1814    zna = TRIM(na)
1815    ! Checks action
1816    IF(ANY(ap_actions == ac).OR.ac == ap_undef) THEN
1817      this%paction = ac
1818    ELSE
1819      ret = error(eprf//" (action)",-9) ; RETURN
1820    ENDIF
1821    ! Checks and sets type and default as a function of the action
1822    SELECT CASE(this%paction)
1823      ! HELP: fixed in any case:
1824      CASE(ap_help)
1825        this%default = 'F'
1826        this%ptype = ap_logical
1827        this%nrec = 0
1828      ! COUNT:
1829      ! we always use "hard-coded" stuff and do not warn if dev has made
1830      ! mistakes...
1831      CASE(ap_count)
1832        ! default settings of the count action
1833        this%ptype = ap_integer ; this%default = '0' ; this%nrec = 0
1834        ! check and set default value
1835        ret = set_def_val()
1836      ! STORE, APPEND actions
1837      CASE (ap_store, ap_append)
1838        ! set type
1839        IF (ty == ap_undef) THEN
1840          this%ptype= ap_integer
1841        ELSEIF (ANY(ap_types == ty)) THEN
1842          this%ptype = ty
1843        ELSE
1844          ret = uty ; RETURN
1845        ENDIF
1846        ! check and set default value
1847        ret = set_def_val() ; IF (ret /= 0) RETURN
1848        ! check for nargs (if na is empty then we set "*")
1849        ret = set_nrec("*")
1850      ! UNDEFINED:
1851      !   -> 1) set to action to store
1852      !   ->
1853      ! try to define a logical trigger and modifies it with user-defined
1854      ! characteristics
1855      CASE (ap_undef)
1856        ! 1) always define store action
1857        this%paction = ap_store
1858        ! 2) set type and nrec:
1859        !    2.1) If type is undef:
1860        !         - to default value type if default is given
1861        !         - ap_logical otherwiset type
1862        !    2.2) set nrec
1863        !        - if final type is ap_logical set nrec to 0
1864        !        - otherwise to *
1865        If (ty == ap_undef) THEN
1866          ! no explicit type : define logical trigger first
1867          this%ptype = ap_logical ; this%nrec = 0
1868          ! icheck the default value given
1869          IF (LEN_TRIM(de) > 0) THEN
1870            this%ptype = ap_types(string_is(de)+1)
1871          ELSE
1872            this%ptype = ap_logical
1873          ENDIF
1874          IF (this%ptype == ap_logical) THEN
1875            ret = set_nrec("0")
1876          ELSE
1877            ret = set_nrec("1")
1878          ENDIF
1879          ret = set_def_val()
1880          IF (ret /= 0) RETURN
1881        ! type is given
1882        ELSE IF (ANY(ty == ap_types)) THEN
1883          ! known type given :
1884          !  check default value and nrec: -> if na not given set "*"
1885          this%ptype = ty
1886          ret = set_def_val() ; IF (ret /= 0) RETURN
1887          IF (this%ptype == ap_logical) THEN
1888            ret = set_nrec("0")
1889          ELSE
1890            ret = set_nrec("1")
1891          ENDIF
1892        ELSE
1893          ! unknown type => bad end !
1894          ret = uty ; RETURN
1895        ENDIF
1896    END SELECT
1897    ! set default value as first value if ret is noerror ....
1898    IF (ret == 0) CALL words_append(this%values,this%default)
1899    RETURN
1900
1901    CONTAINS
1902
1903      FUNCTION set_nrec(base) RESULT(terr)
1904        !! Check and set argument's expected number of records
1905        !! The method compares `na` value with the expected and known flags and decides
1906        !! wether to raise an error or defines nrec member of the argument object. If `na`
1907        !! is empty then `base` is used.
1908        CHARACTER(len=1),INTENT(in) :: base
1909          !! Base value of nrec
1910        TYPE(error) :: terr
1911          !! Error object with the return status of the function
1912        terr = noerror
1913        ! check for nargs:
1914        IF (LEN(zna) == 0) zna=base
1915        SELECT CASE(zna)
1916          CASE("*") ; this%nrec = -1
1917          CASE("+") ; this%nrec = -2
1918          CASE("?") ; this%nrec = -3
1919            IF (this%paction == ap_append) terr = ina
1920          CASE DEFAULT ; this%nrec = 0
1921            ! check numeric characters
1922            IF (VERIFY(zna,"0123456789")==0) READ(zna,*) this%nrec
1923            IF (this%nrec == 0) terr = ina
1924        END SELECT
1925      END FUNCTION set_nrec
1926
1927      FUNCTION set_def_val() RESULT(terr)
1928        !! Check and set argument's default value
1929        !! The method compares `de` value with the type already stored in the argument and
1930        !! decides wether to raise an error or to save `de` as argument's default value.
1931        !! If `de` is empty then it sets a default value according to argument's type.
1932        TYPE(error) :: terr
1933          !! Error object with the return status of the function
1934        INTEGER :: t
1935        terr = noerror
1936        IF (LEN_TRIM(de) /= 0) THEN
1937          this%default = de ; t = string_is(de)
1938          IF (t /= this%ptype) THEN
1939            terr = error(eprf//" (inconsistent default value: expected '"// &
1940                           TRIM(st_type_names(this%ptype))//"', found '"// &
1941                           TRIM(st_type_names(t))//"')",-9)
1942            RETURN
1943          ENDIF
1944        ELSE
1945          SELECT CASE (this%ptype)
1946            CASE(ap_string)  ; this%default = ''
1947            CASE(ap_logical) ; this%default = 'F'
1948            CASE(ap_complex) ; this%default = '(0d0,0d0)'
1949            CASE(ap_integer) ; this%default = '0'
1950            CASE(ap_real)    ; this%default = '0d0'
1951          END SELECT
1952        ENDIF
1953        RETURN
1954      END FUNCTION set_def_val
1955  END FUNCTION ac_check_ac_ty_de_na
1956
1957  FUNCTION ac_check_flags(this,sflag,lflag) RESULT(ret)
1958    !! Set and check if argument's option flags are valid
1959    !! The method first sets the given flags in the argc object and then checks if
1960    !! its option flags are valid :
1961    !!    - A valid short option flag (`sflag`) starts with `-' followed by the
1962    !!      regex pattern : @p [a-zA-Z]
1963    !!    - A valid long option flag (`lflag`) starts with `--' followed by the
1964    !!      regex pattern : @p [-a-zA-Z_0-9]+
1965    !! @note
1966    !! Although the two arguments are mandatory one can be an empty string
1967    TYPE(argc), INTENT(inout)    :: this
1968      !! An argc object
1969    CHARACTER(len=2), INTENT(in) :: sflag
1970      !! A 2-characters wide string with the short option flag
1971    CHARACTER(len=*), INTENT(in) :: lflag
1972      !! A string (at least 3 characters wide) with the long option flag
1973    TYPE(error) :: ret
1974      !! Error object with the first error encountered in the process
1975    INTEGER :: ic
1976    ret = noerror
1977    this%sflag = sflag ; this%lflag = lflag
1978    ! 1) Check null strings !
1979    IF (LEN_TRIM(this%sflag) == 0 .AND. LEN_TRIM(this%lflag) == 0) THEN
1980      ret = error("argparse: Invalid argument (empty option flags)",-2) ; RETURN
1981    ENDIF
1982    ! 2) Check short option flag:
1983    IF (LEN_TRIM(this%sflag) > 0) THEN
1984      IF (this%sflag(1:1) /= achar(45)) THEN
1985        ret = error("argparse: Invalid argument (short option)",-2) ; RETURN
1986      ELSE
1987        SELECT CASE(iachar(this%sflag(2:2)))
1988          CASE(97:122,65:90) ; ret = noerror
1989          CASE DEFAULT
1990            ret = error("argparse: Invalid argument (short option)",-2) ; RETURN
1991        END SELECT
1992      ENDIF
1993    ENDIF
1994    ! 3) Check long option flag
1995    IF (LEN_TRIM(this%lflag) > 0) THEN
1996      ! We must have at least 3 chars !
1997      IF (LEN_TRIM(this%lflag) < 3) THEN
1998        ret = error("argparse: Invalid argument (long option)",-2) ; RETURN
1999      ELSE IF (this%lflag(1:2) /= achar(45)//achar(45)) THEN
2000        ret = error("argparse: Invalid argument (long option)",-2) ; RETURN
2001      ELSE
2002        DO ic=3,LEN_TRIM(this%lflag)
2003          SELECT CASE(iachar(this%lflag(ic:ic)))
2004            !  corresponds to [-a-zA-Z0-9_]
2005            CASE(45,48:57,65:90,95,97:122) ; ret = noerror
2006            CASE DEFAULT
2007              ret = error("argparse: Invalid argument (long option)",-2) ; RETURN
2008              EXIT
2009          END SELECT
2010        ENDDO
2011      ENDIF
2012    ENDIF
2013    RETURN
2014  END FUNCTION ac_check_flags
2015
2016  SUBROUTINE ac_set_meta(this, meta)
2017    !! Set meta-variable of the given argc object
2018    !! The method set meta-variable in the argc object. If no `meta` are given, the method
2019    !! uses argument's name to set the values.
2020    !! @warning
2021    !! To be effective, this subroutine must be called after argparse::chk_opt_nargs
2022    TYPE(argc), INTENT(inout)                            :: this
2023      !! An argc object reference
2024    CHARACTER(len=*), INTENT(in), DIMENSION(:), OPTIONAL :: meta
2025      !! An optional vector of strings with the meta-variable(s) to set
2026    INTEGER                       :: i,j,ms,blk
2027    CHARACTER(len=:), ALLOCATABLE :: zmeta
2028    ! clear meta values (not needed normally)
2029    CALL words_clear(this%meta)
2030    IF (PRESENT(meta)) THEN
2031      SELECT CASE(this%nrec)
2032        CASE(-3,-2,-1)
2033          zmeta = to_upper(meta(1))
2034          blk = INDEX(TRIM(zmeta),CHAR(32)) - 1
2035          IF (blk <= 0) blk=LEN_TRIM(zmeta)
2036          CALL words_append(this%meta,zmeta(1:blk))
2037        CASE(0)
2038          CALL words_append(this%meta,"")
2039        CASE DEFAULT
2040          ms = SIZE(meta) ; j = 0
2041          DO i=1,this%nrec
2042            j=j+1 ; IF (j>ms) j=1
2043            zmeta = to_upper(meta(j))
2044            blk=INDEX(TRIM(zmeta),CHAR(32))-1
2045            IF (blk <= 0) blk=LEN_TRIM(zmeta)
2046            CALL words_append(this%meta,zmeta(1:blk))
2047          ENDDO
2048      END SELECT
2049    ELSE
2050      zmeta = to_upper(TRIM(this%name))
2051      SELECT CASE(this%nrec)
2052        CASE(-3,-2,-1)
2053          CALL words_append(this%meta,zmeta)
2054        CASE DEFAULT
2055          DO i=1,this%nrec
2056            CALL words_append(this%meta,zmeta)
2057          ENDDO
2058      END SELECT
2059    ENDIF
2060    RETURN
2061  END SUBROUTINE ac_set_meta
2062
2063  FUNCTION ac_check_value(this,str) RESULT(err)
2064    !! Check if given string is a valid value for the argument
2065    TYPE(argc), INTENT(in)       :: this
2066      !! An argc object reference
2067    CHARACTER(len=*), INTENT(in) :: str
2068      !! A string with the value to check
2069    TYPE(error) :: err
2070      !! Error object with the first error encountered in the process
2071    INTEGER :: ty
2072    err = noerror
2073    ! Special conditions for strings: any kind of value is ok if we asked for
2074    ! strings
2075    IF (this%ptype == ap_string) RETURN
2076    ty = string_is(str)
2077    ! special handling for integer: they can be seen as real
2078    IF (this%ptype == ap_real) THEN
2079      IF (ty < 3)  err = error("Cannot cast value",-10)
2080    ELSE
2081      IF (ty /= this%ptype) err = error("Cannot cast value",-10)
2082    ENDIF
2083    RETURN
2084  END FUNCTION ac_check_value
2085
2086  !===========
2087  !  GETTERS
2088  !===========
2089
2090  ! argparser getters
2091  ! -----------------
2092
2093  FUNCTION ap_get_positional_sc(this,idx,value) RESULT(ret)
2094    !! Get positional arguments value at given index
2095    !! @warning
2096    !! On error, the status of `value` is undefined.
2097    OBJECT(argparser), INTENT(in)              :: this
2098      !! An argparser object reference
2099    INTEGER, INTENT(in)                        :: idx
2100      !! Subscript of the positional argument value to get
2101    CHARACTER(len=:), INTENT(out), ALLOCATABLE :: value
2102      !! Output raw value of the positional. If `idx` is out of range, `value` is set to an
2103      !! empty string.
2104    TYPE(error) :: ret
2105      !! Error object with the first error encountered in the process
2106    IF (.NOT.this%have_posal) THEN
2107      ret = error("argparse: No positional argument(s) defined",-7)
2108    ELSE IF (idx <= 0 .OR. idx > words_length(this%posals%values)) THEN
2109      ret = error("argparse: index out of range", -3)
2110    ELSE
2111      value = words_get(this%posals%values,idx)
2112      ret = noerror
2113    ENDIF
2114    RETURN
2115  END FUNCTION ap_get_positional_sc
2116
2117  FUNCTION ap_get_positional_ve(this,values) RESULT(ret)
2118    !! Get all positional arguments value
2119    !! @warning
2120    !! On error, the status of `values` is undefined.
2121    OBJECT(argparser), INTENT(in)                                  :: this
2122      !! An argparser object reference
2123    CHARACTER(len=st_slen), INTENT(out), ALLOCATABLE, DIMENSION(:) :: values
2124      !! An allocatable vector of **assumed length** strings with the value(s) of all
2125      !! positionals arguments found.
2126    TYPE(error) :: ret
2127      !! Error object with the first error encountered in the process
2128    LOGICAL :: ok
2129    ret = noerror
2130    IF (.NOT.this%have_posal) THEN
2131      ret = error("argparse: No positional argument(s) defined",-7)
2132    ELSE IF (words_length(this%posals%values) == 0) THEN
2133      ret = error("argparse: No positional argument(s) values found",-6)
2134    ELSE
2135      ok = words_to_vector(this%posals%values,values)
2136    ENDIF
2137    RETURN
2138  END FUNCTION ap_get_positional_ve
2139
2140  FUNCTION ap_get_dv_sc(this, name, output) RESULT(ret)
2141    !! Get a scalar `REAL(kind=8)` value from given argument
2142    !! The error returned by the method can be either:
2143    !! -  0  : No error
2144    !! - -1  : parser has not been initialized
2145    !! - -7  : argument not found (i.e. does not set in the parser)
2146    !! - -19 : parsing not done yet
2147    !! - -20 : (previous) parsing failed
2148    !! - -21 : inconsistent destination type
2149    !! @note
2150    !! If no error occured, the function always set a value which is the default value
2151    !! if the argument has not been parsed. Otherwise, `output` value is undefined.
2152    OBJECT(argparser), INTENT(in) :: this
2153      !! An argparser object reference
2154    CHARACTER(len=*), INTENT(in)  :: name
2155      !! Name of the argument
2156    REAL(kind=8), INTENT(out)     :: output
2157      !! A scalar with the first value of the argument
2158    TYPE(error) :: ret
2159      !! Error object with the first error encountered in the process
2160    INTEGER :: idx
2161    ret = ap_check_state(this)
2162    IF (ret == 0) THEN
2163      idx = ap_get_arg_index(this,name)
2164      IF (idx == -1) THEN
2165        ret = error("argparse: Argument not found ("//TRIM(name)//")",-7)
2166      ELSE
2167        ret = argc_get_value(this%args(idx),output)
2168      ENDIF
2169    ENDIF
2170    RETURN
2171  END FUNCTION ap_get_dv_sc
2172
2173  FUNCTION ap_get_rv_sc(this, name, output) RESULT(ret)
2174    !! Get a scalar `REAL(kind=4)` value from given argument
2175    !! The error returned by the method can be either:
2176    !! -  0  : No error
2177    !! - -1  : parser has not been initialized
2178    !! - -7  : argument not found (i.e. does not set in the parser)
2179    !! - -19 : parsing not done yet
2180    !! - -20 : (previous) parsing failed
2181    !! - -21 : inconsistent destination type
2182    !! @note
2183    !! If no error occured, the function always set a value which is the default value
2184    !! if the argument has not been parsed. Otherwise, `output` value is undefined.
2185    OBJECT(argparser), INTENT(in) :: this
2186      !! An argparser object reference
2187    CHARACTER(len=*), INTENT(in)  :: name
2188      !! Name of the argument
2189    REAL(kind=4), INTENT(out)     :: output
2190      !! A scalar with the first value of the argument
2191    TYPE(error) :: ret
2192      !! Error object with the first error encountered in the process
2193    INTEGER :: idx
2194    ret = ap_check_state(this)
2195    IF (ret == 0) THEN
2196      idx = ap_get_arg_index(this,name)
2197      IF (idx == -1) THEN
2198        ret = error("argparse: Argument not found ("//TRIM(name)//")",-7)
2199      ELSE
2200        ret = argc_get_value(this%args(idx),output)
2201      ENDIF
2202    ENDIF
2203    RETURN
2204  END FUNCTION ap_get_rv_sc
2205
2206  FUNCTION ap_get_iv_sc(this, name, output) RESULT(ret)
2207    !! Get a scalar `INTEGER` value from given argument
2208    !! The error returned by the method can be either:
2209    !! -  0  : No error
2210    !! - -1  : parser has not been initialized
2211    !! - -7  : argument not found (i.e. does not set in the parser)
2212    !! - -19 : parsing not done yet
2213    !! - -20 : (previous) parsing failed
2214    !! - -21 : inconsistent destination type
2215    !! @note
2216    !! If no error occured, the function always set a value which is the default value
2217    !! if the argument has not been parsed. Otherwise, `output` value is undefined.
2218    OBJECT(argparser), INTENT(in) :: this
2219      !! An argparser object reference
2220    CHARACTER(len=*), INTENT(in)  :: name
2221      !! Name of the argument
2222    INTEGER, INTENT(out)          :: output
2223      !! A scalar with the first value of the argument
2224    TYPE(error) :: ret
2225      !! Error object with the first error encountered in the process
2226    INTEGER :: idx
2227    ret = ap_check_state(this)
2228    IF (ret == 0) THEN
2229      idx = ap_get_arg_index(this,name)
2230      IF (idx == -1) THEN
2231        ret = error("argparse: Argument not found ("//TRIM(name)//")",-7)
2232      ELSE
2233        ret = argc_get_value(this%args(idx),output)
2234      ENDIF
2235    ENDIF
2236    RETURN
2237  END FUNCTION ap_get_iv_sc
2238
2239  FUNCTION ap_get_lv_sc(this, name, output) RESULT(ret)
2240    !! Get a scalar `LOGICAL` value from given argument
2241    !! The error returned by the method can be either:
2242    !! -  0  : No error
2243    !! - -1  : parser has not been initialized
2244    !! - -7  : argument not found (i.e. does not set in the parser)
2245    !! - -19 : parsing not done yet
2246    !! - -20 : (previous) parsing failed
2247    !! - -21 : inconsistent destination type
2248    !! @note
2249    !! If no error occured, the function always set a value which is the default value
2250    !! if the argument has not been parsed. Otherwise, `output` value is undefined.
2251    OBJECT(argparser), INTENT(in) :: this
2252      !! An argparser object reference
2253    CHARACTER(len=*), INTENT(in)  :: name
2254      !! Name of the argument
2255    LOGICAL, INTENT(out)          :: output
2256      !! A scalar with the first value of the argument
2257    TYPE(error) :: ret
2258      !! Error object with the first error encountered in the process
2259    INTEGER :: idx
2260    ret = ap_check_state(this)
2261    IF (ret == 0) THEN
2262      idx = ap_get_arg_index(this,name)
2263      IF (idx == -1) THEN
2264        ret = error("argparse: Argument not found ("//TRIM(name)//")",-7)
2265      ELSE
2266        ret = argc_get_value(this%args(idx),output)
2267      ENDIF
2268    ENDIF
2269    RETURN
2270  END FUNCTION ap_get_lv_sc
2271
2272  FUNCTION ap_get_cv_sc(this, name, output) RESULT(ret)
2273    !! Get a scalar `COMPLEX` value from given argument
2274    !! The error returned by the method can be either:
2275    !! -  0  : No error
2276    !! - -1  : parser has not been initialized
2277    !! - -7  : argument not found (i.e. does not set in the parser)
2278    !! - -19 : parsing not done yet
2279    !! - -20 : parsing failed
2280    !! - -21 : inconsistent destination type
2281    !! @note
2282    !! If no error occured, the function always set a value which is the default value
2283    !! if the argument has not been parsed. Otherwise, `output` value is undefined.
2284    OBJECT(argparser), INTENT(in) :: this
2285      !! An argparser object reference
2286    CHARACTER(len=*), INTENT(in)  :: name
2287      !! Name of the argument
2288    COMPLEX, INTENT(out)          :: output
2289      !! A scalar with the first value of the argument
2290    TYPE(error) :: ret
2291      !! Error object with the first error encountered in the process
2292    INTEGER :: idx
2293    ret = ap_check_state(this)
2294    IF (ret == 0) THEN
2295      idx = ap_get_arg_index(this,name)
2296      IF (idx == -1) THEN
2297        ret = error("argparse: Argument not found ("//TRIM(name)//")",-7)
2298      ELSE
2299        ret = argc_get_value(this%args(idx),output)
2300      ENDIF
2301    ENDIF
2302    RETURN
2303  END FUNCTION ap_get_cv_sc
2304
2305  FUNCTION ap_get_sv_sc(this, name, output) RESULT(ret)
2306    !! Get a scalar `STRING` value from given argument
2307    !! The error returned by the method can be either:
2308    !! -  0  : No error
2309    !! - -1  : parser has not been initialized
2310    !! - -7  : argument not found (i.e. does not set in the parser)
2311    !! - -19 : parsing not done yet
2312    !! - -20 : (previous) parsing failed
2313    !! - -21 : inconsistent destination type
2314    !! @note
2315    !! If no error occured, the function always set a value which is the default value
2316    !! if the argument has not been parsed. Otherwise, `output` status is undefined.
2317    OBJECT(argparser), INTENT(in)              :: this
2318      !! An argparser object reference
2319    CHARACTER(len=*), INTENT(in)               :: name
2320      !! Name of the argument
2321    CHARACTER(len=:), INTENT(out), ALLOCATABLE :: output
2322      !! An allocatable string with the first value of the argument
2323    TYPE(error) :: ret
2324      !! Error object with the first error encountered in the process
2325    INTEGER :: idx
2326    ret = ap_check_state(this)
2327    IF (ret == 0) THEN
2328      idx = ap_get_arg_index(this,name)
2329      IF (idx == -1) THEN
2330        ret = error("argparse: Argument not found ("//TRIM(name)//")",-7)
2331      ELSE
2332        ret = argc_get_value(this%args(idx),output)
2333      ENDIF
2334    ENDIF
2335    RETURN
2336  END FUNCTION ap_get_sv_sc
2337
2338  FUNCTION ap_get_dv_ve(this, name, output) RESULT(ret)
2339    !! Get a vector of `REAL(kind=8)` values from given argument
2340    !! The error returned by the method can be either:
2341    !! -  0  : No error
2342    !! - -1  : parser has not been initialized
2343    !! - -7  : argument not found (i.e. does not set in the parser)
2344    !! - -19 : parsing not done yet
2345    !! - -20 : (previous) parsing failed
2346    !! - -21 : inconsistent destination type
2347    !! @note
2348    !! If no error occured, the function always set a value which is the default value
2349    !! if the argument has not been parsed. Otherwise, `output` status is undefined.
2350    OBJECT(argparser), INTENT(in)                        :: this
2351      !! An argparser object reference
2352    CHARACTER(len=*), INTENT(in)                         :: name
2353      !! Name of the argument
2354    REAL(kind=8), INTENT(out), ALLOCATABLE, DIMENSION(:) :: output
2355      !! An allocatable vector with the values of the argument
2356    TYPE(error) :: ret
2357      !! Error object with the first error encountered in the process
2358    INTEGER :: idx
2359    ret = ap_check_state(this)
2360    IF (ret == 0) THEN
2361      idx = ap_get_arg_index(this,name)
2362      IF (idx == -1) THEN
2363        ret = error("argparse: Argument not found ("//TRIM(name)//")",-7)
2364      ELSE
2365        ret = argc_get_value(this%args(idx),output)
2366      ENDIF
2367    ENDIF
2368  END FUNCTION ap_get_dv_ve
2369
2370  FUNCTION ap_get_rv_ve(this, name, output) RESULT(ret)
2371    !! Get a vector of `REAL(kind=4)` values from given argument
2372    !! The error returned by the method can be either:
2373    !! -  0  : No error
2374    !! - -1  : parser has not been initialized
2375    !! - -7  : argument not found (i.e. does not set in the parser)
2376    !! - -19 : parsing not done yet
2377    !! - -20 : (previous) parsing failed
2378    !! - -21 : inconsistent destination type
2379    !! @note
2380    !! If no error occured, the function always set a value which is the default value
2381    !! if the argument has not been parsed. Otherwise, `output` status is undefined.
2382    OBJECT(argparser), INTENT(in)                        :: this
2383      !! An argparser object reference
2384    CHARACTER(len=*), INTENT(in)                         :: name
2385      !! Name of the argument
2386    REAL(kind=4), INTENT(out), ALLOCATABLE, DIMENSION(:) :: output
2387      !! An allocatable vector with the values of the argument
2388    TYPE(error) :: ret
2389      !! Error object with the first error encountered in the process
2390    INTEGER :: idx
2391    ret = ap_check_state(this)
2392    IF (ret == 0) THEN
2393      idx = ap_get_arg_index(this,name)
2394      IF (idx == -1) THEN
2395        ret = error("argparse: Argument not found ("//TRIM(name)//")",-7)
2396      ELSE
2397        ret = argc_get_value(this%args(idx),output)
2398      ENDIF
2399    ENDIF
2400  END FUNCTION ap_get_rv_ve
2401
2402  FUNCTION ap_get_iv_ve(this, name, output) RESULT(ret)
2403    !! Get a vector of `INTEGER` values from given argument
2404    !! The error returned by the method can be either:
2405    !! -  0  : No error
2406    !! - -1  : parser has not been initialized
2407    !! - -7  : argument not found (i.e. does not set in the parser)
2408    !! - -19 : parsing not done yet
2409    !! - -20 : (previous) parsing failed
2410    !! - -21 : inconsistent destination type
2411    !! @note
2412    !! If no error occured, the function always set a value which is the default value
2413    !! if the argument has not been parsed. Otherwise, `output` status is undefined.
2414    OBJECT(argparser), INTENT(in)                   :: this
2415      !! An argparser object reference
2416    CHARACTER(len=*), INTENT(in)                    :: name
2417      !! Name of the argument
2418    INTEGER, INTENT(out), ALLOCATABLE, DIMENSION(:) :: output
2419      !! An allocatable vector with the values of the argument
2420    TYPE(error) :: ret
2421      !! Error object with the first error encountered in the process
2422    INTEGER :: idx
2423    ret = ap_check_state(this)
2424    IF (ret == 0) THEN
2425      idx = ap_get_arg_index(this,name)
2426      IF (idx == -1) THEN
2427        ret = error("argparse: Argument not found ("//TRIM(name)//")",-7)
2428      ELSE
2429        ret = argc_get_value(this%args(idx),output)
2430      ENDIF
2431    ENDIF
2432  END FUNCTION ap_get_iv_ve
2433
2434  FUNCTION ap_get_lv_ve(this, name, output) RESULT(ret)
2435    !! Get a vector of `LOGICAL` values from given argument
2436    !! The error returned by the method can be either:
2437    !! -  0  : No error
2438    !! - -1  : parser has not been initialized
2439    !! - -7  : argument not found (i.e. does not set in the parser)
2440    !! - -19 : parsing not done yet
2441    !! - -20 : (previous) parsing failed
2442    !! - -21 : inconsistent destination type
2443    !! @note
2444    !! If no error occured, the function always set a value which is the default value
2445    !! if the argument has not been parsed. Otherwise, `output` status is undefined.
2446    OBJECT(argparser), INTENT(in)                   :: this
2447      !! An argparser object reference
2448    CHARACTER(len=*), INTENT(in)                    :: name
2449      !! Name of the argument
2450    LOGICAL, INTENT(out), ALLOCATABLE, DIMENSION(:) :: output
2451      !! An allocatable vector with the values of the argument
2452    TYPE(error) :: ret
2453      !! Error object with the first error encountered in the process
2454    INTEGER :: idx
2455    ret = ap_check_state(this)
2456    IF (ret == 0) THEN
2457      idx = ap_get_arg_index(this,name)
2458      IF (idx == -1) THEN
2459        ret = error("argparse: Argument not found ("//TRIM(name)//")",-7)
2460      ELSE
2461        ret = argc_get_value(this%args(idx),output)
2462      ENDIF
2463    ENDIF
2464  END FUNCTION ap_get_lv_ve
2465
2466  FUNCTION ap_get_cv_ve(this, name, output) RESULT(ret)
2467    !! Get a vector of `COMPLEX` values from given argument
2468    !! The error returned by the method can be either:
2469    !! -  0  : No error
2470    !! - -1  : parser has not been initialized
2471    !! - -7  : argument not found (i.e. does not set in the parser)
2472    !! - -19 : parsing not done yet
2473    !! - -20 : (previous) parsing failed
2474    !! - -21 : inconsistent destination type
2475    !! @note
2476    !! If no error occured, the function always set a value which is the default value
2477    !! if the argument has not been parsed. Otherwise, `output` status is undefined.
2478    OBJECT(argparser), INTENT(in)                   :: this
2479      !! An argparser object reference
2480    CHARACTER(len=*), INTENT(in)                    :: name
2481      !! Name of the argument
2482    COMPLEX, INTENT(out), ALLOCATABLE, DIMENSION(:) :: output
2483      !! An allocatable vector with the values of the argument
2484    TYPE(error) :: ret
2485      !! Error object with the first error encountered in the process
2486    INTEGER :: idx
2487    ret = ap_check_state(this)
2488    IF (ret == 0) THEN
2489      idx = ap_get_arg_index(this,name)
2490      IF (idx == -1) THEN
2491        ret = error("argparse: Argument not found ("//TRIM(name)//")",-7)
2492      ELSE
2493        ret = argc_get_value(this%args(idx),output)
2494      ENDIF
2495    ENDIF
2496  END FUNCTION ap_get_cv_ve
2497
2498  FUNCTION ap_get_sv_ve(this, name, output) RESULT(ret)
2499    !! Get a vector of `STRING` values from given argument
2500    !! The error returned by the method can be either:
2501    !! -  0  : No error
2502    !! - -1  : parser has not been initialized
2503    !! - -7  : argument not found (i.e. does not set in the parser)
2504    !! - -19 : parsing not done yet
2505    !! - -20 : (previous) parsing failed
2506    !! - -21 : inconsistent destination type
2507    !! @note
2508    !! If no error occured, the function always set a value which is the default value
2509    !! if the argument has not been parsed. Otherwise, `output` status is undefined.
2510    OBJECT(argparser), INTENT(in)                            :: this
2511      !! An argparser object reference
2512    CHARACTER(len=*), INTENT(in)                             :: name
2513      !! Name of the argument
2514    CHARACTER(len=*), INTENT(out), ALLOCATABLE, DIMENSION(:) :: output
2515      !! An allocatable vector of **assumed length** strings with the values of the argument
2516    TYPE(error) :: ret
2517      !! Error object with the first error encountered in the process
2518    INTEGER :: idx
2519    ret = ap_check_state(this)
2520    IF (ret == 0) THEN
2521      idx = ap_get_arg_index(this,name)
2522      IF (idx == -1) THEN
2523        ret = error("argparse: Argument not found ("//TRIM(name)//")",-7)
2524      ELSE
2525        ret = argc_get_value(this%args(idx),output)
2526      ENDIF
2527    ENDIF
2528  END FUNCTION ap_get_sv_ve
2529
2530  ! argc getters
2531  ! ------------
2532
2533  !> Gets a scalar @p REAL(kind=8) value from given argument
2534  !! @param[in,out] this An argc object
2535  !! @param[out] output A scalar with the first value of the argument
2536  !! @return An errors::error object with -21 if the destination variable's type
2537  !! is inconsistent, 0 otherwise.
2538  FUNCTION ac_get_dv_sc(this, output) RESULT(ret)
2539    !! Get a scalar `REAL(kind=8)` value from given argument
2540    !! If no error occured, the function always returns at least a value (whatever the parser's
2541    !! state is) which is the default value if no specific values are set in the argument.
2542    !! Otherwise, `output` value is undefined.
2543    TYPE(argc), INTENT(in)  :: this
2544      !! An argc object
2545    REAL(kind=8), INTENT(out) :: output
2546      !! Output value
2547    TYPE(error) :: ret
2548      !! Error object with the -21 if the destination variable's type is inconsistent, 0 otherwise
2549    ret = noerror
2550    IF (this%ptype /= ap_real) THEN
2551      ret = error("argparse: invalid type for output (expected `"// &
2552                  apt2str(this%ptype)//"' got REAL(kind=8))",-21)
2553    ELSEIF (words_length(this%values) == 0) THEN
2554      IF (.NOT.from_string(this%default,output)) &
2555        ret = error("Cannot cast value",-10)
2556    ELSE
2557      IF (.NOT.from_string(words_get(this%values,1), output)) &
2558        ret = error("Cannot cast value",-10)
2559    ENDIF
2560    RETURN
2561  END FUNCTION ac_get_dv_sc
2562
2563  FUNCTION ac_get_rv_sc(this, output) RESULT(ret)
2564    !! Get a scalar `REAL(kind=4)` value from given argument
2565    !! If no error occured, the function always returns at least a value (whatever the parser's
2566    !! state is) which is the default value if no specific values are set in the argument.
2567    !! Otherwise, `output` value is undefined.
2568    TYPE(argc), INTENT(in)    :: this
2569      !! An argc object
2570    REAL(kind=4), INTENT(out) :: output
2571      !! Output value
2572    TYPE(error) :: ret
2573      !! Error object with the first error encountered in the process
2574    ret = noerror
2575    IF (this%ptype /= ap_real) THEN
2576      ret = error("argparse: invalid type for output (expected `"// &
2577                  apt2str(this%ptype)//"' got REAL(kind=4))",-21)
2578    ELSEIF (words_length(this%values) == 0) THEN
2579      IF (.NOT.from_string(this%default,output)) &
2580        ret = error("Cannot cast value",-10)
2581    ELSE
2582      IF (.NOT.from_string(words_get(this%values,1), output)) &
2583        ret = error("Cannot cast value",-10)
2584    ENDIF
2585    RETURN
2586  END FUNCTION ac_get_rv_sc
2587
2588  FUNCTION ac_get_iv_sc(this, output) RESULT(ret)
2589    !! Get a scalar `INTEGER` value from given argument
2590    !! If no error occured, the function always returns at least a value (whatever the parser's
2591    !! state is) which is the default value if no specific values are set in the argument.
2592    !! Otherwise, `output` value is undefined.
2593    TYPE(argc), INTENT(in) :: this
2594      !! An argc object
2595    INTEGER, INTENT(out)   :: output
2596      !! Output value
2597    TYPE(error) :: ret
2598      !! Error object with the first error encountered in the process
2599    ret = noerror
2600    IF (this%ptype /= ap_integer) THEN
2601      ret = error("argparse: invalid type for output (expected `"// &
2602                  apt2str(this%ptype)//"' got INTEGER)",-21)
2603    ELSEIF (words_length(this%values) == 0) THEN
2604      IF (.NOT.from_string(this%default,output)) &
2605        ret = error("Cannot cast value",-10)
2606    ELSE
2607      IF (.NOT.from_string(words_get(this%values,1), output)) &
2608        ret = error("Cannot cast value",-10)
2609    ENDIF
2610    RETURN
2611  END FUNCTION ac_get_iv_sc
2612
2613  FUNCTION ac_get_lv_sc(this, output) RESULT(ret)
2614    !! Get a scalar `INTEGER` value from given argument
2615    !! If no error occured, the function always returns at least a value (whatever the parser's
2616    !! state is) which is the default value if no specific values are set in the argument.
2617    !! Otherwise, `output` value is undefined.
2618    TYPE(argc), INTENT(in) :: this
2619      !! An argc object
2620    LOGICAL, INTENT(out)   :: output
2621      !! Output value
2622    TYPE(error) :: ret
2623      !! Error object with the first error encountered in the process
2624    ret = noerror
2625    IF (this%ptype /= ap_logical) THEN
2626      ret = error("argparse: invalid type for output (expected `"// &
2627                  apt2str(this%ptype)//"' got LOGICAL)",-21)
2628    ELSEIF (words_length(this%values) == 0) THEN
2629      IF (.NOT.from_string(this%default,output)) &
2630        ret = error("Cannot cast value",-10)
2631    ELSE
2632      IF (.NOT.from_string(words_get(this%values,1), output)) &
2633        ret = error("Cannot cast value",-10)
2634    ENDIF
2635    RETURN
2636  END FUNCTION ac_get_lv_sc
2637
2638  FUNCTION ac_get_cv_sc(this, output) RESULT(ret)
2639    !! Get a scalar `COMPLEX` value from given argument
2640    !! If no error occured, the function always returns at least a value (whatever the parser's
2641    !! state is) which is the default value if no specific values are set in the argument.
2642    !! Otherwise, `output` value is undefined.
2643    TYPE(argc), INTENT(in) :: this
2644      !! An argc object
2645    COMPLEX, INTENT(out)   :: output
2646      !! Ouput value
2647    TYPE(error) :: ret
2648      !! Error object with the first error encountered in the process
2649    ret = noerror
2650    IF (this%ptype /= ap_complex) THEN
2651      ret = error("argparse: invalid type for output (expected `"// &
2652                  apt2str(this%ptype)//"' got COMPLEX)",-21)
2653    ELSEIF (words_length(this%values) == 0) THEN
2654      IF (.NOT.from_string(this%default,output)) &
2655        ret = error("Cannot cast value",-10)
2656    ELSE
2657      IF (.NOT.from_string(words_get(this%values,1), output)) &
2658        ret = error("Cannot cast value",-10)
2659    ENDIF
2660    RETURN
2661  END FUNCTION ac_get_cv_sc
2662
2663  FUNCTION ac_get_sv_sc(this, output) RESULT(ret)
2664    !! Get a scalar `STRING` value from given argument
2665    !! If no error occured, the function always returns at least a value (whatever the parser's
2666    !! state is) which is the default value if no specific values are set in the argument.
2667    !! Otherwise, `output` status is undefined.
2668    TYPE(argc), INTENT(in)                     :: this
2669      !! An argc object
2670    CHARACTER(len=:), INTENT(out), ALLOCATABLE :: output
2671      !! Output value
2672    TYPE(error) :: ret
2673      !! Error object with the first error encountered in the process
2674    ret = noerror
2675    IF (this%ptype /= ap_string) THEN
2676      ret = error("argparse: invalid type for output (expected `"// &
2677                  apt2str(this%ptype)//"' got STRING)",-21)
2678    ELSEIF (words_length(this%values) == 0) THEN
2679      output = this%default
2680    ELSE
2681      output = words_get(this%values,1)
2682    ENDIF
2683  END FUNCTION ac_get_sv_sc
2684
2685  FUNCTION ac_get_dv_ve(this, output) RESULT(ret)
2686    !! Get a vector of `REAL(kind=8)` values from given argument
2687    !! If no error occured, the function always returns at least a value (whatever the parser's
2688    !! state is) which is the default value if no specific values are set in the argument.
2689    !! Otherwise, `output` status is undefined.
2690    TYPE(argc), INTENT(in)                               :: this
2691      !! Argc object
2692    REAL(kind=8), INTENT(out), ALLOCATABLE, DIMENSION(:) :: output
2693      !! Output values
2694    TYPE(error) :: ret
2695      !! Error object with the first error encountered in the process
2696    CHARACTER(len=st_slen), ALLOCATABLE, DIMENSION(:) :: tmp
2697    LOGICAL                                           :: ok
2698    ret = noerror
2699    IF (this%ptype /= ap_real) THEN
2700      ret = error("argparse: invalid type for output (expected `"// &
2701                  apt2str(this%ptype)//"' got REAL(kind=8))",-21)
2702    ELSEIF (words_length(this%values) == 0) THEN
2703      ALLOCATE(output(MAX(this%nrec,1)))
2704      ok = from_string(this%default,output(1))
2705      output(1:SIZE(output)) = output(1)
2706    ELSE
2707      IF (ALLOCATED(output)) DEALLOCATE(output)
2708      ALLOCATE(output(words_length(this%values)))
2709      ok = words_to_vector(this%values,tmp)
2710      ok = from_string(tmp, output)
2711    ENDIF
2712  END FUNCTION ac_get_dv_ve
2713
2714  FUNCTION ac_get_rv_ve(this, output) RESULT(ret)
2715    !! Get a vector of `REAL(kind=4)` values from given argument
2716    !! If no error occured, the function always returns at least a value (whatever the parser's
2717    !! state is) which is the default value if no specific values are set in the argument.
2718    !! Otherwise, `output` status is undefined.
2719    TYPE(argc), INTENT(in)                               :: this
2720      !! Argc object
2721    REAL(kind=4), INTENT(out), ALLOCATABLE, DIMENSION(:) :: output
2722      !! Output values
2723    TYPE(error) :: ret
2724      !! Error object with the first error encountered in the process
2725    CHARACTER(len=st_slen), ALLOCATABLE, DIMENSION(:) :: tmp
2726    LOGICAL                                           :: ok
2727    ret = noerror
2728    IF (this%ptype /= ap_real) THEN
2729      ret = error("argparse: invalid type for output (expected `"// &
2730                  apt2str(this%ptype)//"' got REAL(kind=4))",-21)
2731    ELSEIF (words_length(this%values) == 0) THEN
2732      ALLOCATE(output(MAX(this%nrec,1)))
2733      ok = from_string(this%default,output(1))
2734      output(1:SIZE(output)) = output(1)
2735    ELSE
2736      IF (ALLOCATED(output)) DEALLOCATE(output)
2737      ALLOCATE(output(words_length(this%values)))
2738      ok = words_to_vector(this%values,tmp)
2739      ok = from_string(tmp, output)
2740    ENDIF
2741  END FUNCTION ac_get_rv_ve
2742
2743  FUNCTION ac_get_iv_ve(this, output) RESULT(ret)
2744    !! Get a vector of `INTEGER` values from given argument
2745    !! If no error occured, the function always returns at least a value (whatever the parser's
2746    !! state is) which is the default value if no specific values are set in the argument.
2747    !! Otherwise, `output` status is undefined.
2748    TYPE(argc), INTENT(in)                          :: this
2749      !! Argc object
2750    INTEGER, INTENT(out), ALLOCATABLE, DIMENSION(:) :: output
2751      !! Output values
2752    TYPE(error) :: ret
2753      !! Error object with the first error encountered in the process
2754    CHARACTER(len=st_slen), ALLOCATABLE, DIMENSION(:) :: tmp
2755    LOGICAL                                           :: ok
2756    ret = noerror
2757    IF (this%ptype /= ap_integer) THEN
2758      ret = error("argparse: invalid type for output (expected `"// &
2759                  apt2str(this%ptype)//"' got INTEGER)",-21)
2760    ELSEIF (words_length(this%values) == 0) THEN
2761      ALLOCATE(output(MAX(this%nrec,1)))
2762      ok = from_string(this%default,output(1))
2763      output(1:SIZE(output)) = output(1)
2764    ELSE
2765      IF (ALLOCATED(output)) DEALLOCATE(output)
2766      ALLOCATE(output(words_length(this%values)))
2767      ok = words_to_vector(this%values,tmp)
2768      ok = from_string(tmp, output)
2769    ENDIF
2770  END FUNCTION ac_get_iv_ve
2771
2772  FUNCTION ac_get_lv_ve(this, output) RESULT(ret)
2773    !! Get a vector of `LOGICAL` values from given argument
2774    !! If no error occured, the function always returns at least a value (whatever the parser's
2775    !! state is) which is the default value if no specific values are set in the argument.
2776    !! Otherwise, `output` status is undefined.
2777    TYPE(argc), INTENT(in)                          :: this
2778      !! Argc object
2779    LOGICAL, INTENT(out), ALLOCATABLE, DIMENSION(:) :: output
2780      !! Output values
2781    TYPE(error) :: ret
2782      !! Error object with the first error encountered in the process
2783    CHARACTER(len=st_slen), ALLOCATABLE, DIMENSION(:) :: tmp
2784    LOGICAL                                           :: ok
2785    ret = noerror
2786    IF (this%ptype /= ap_logical) THEN
2787      ret = error("argparse: invalid type for output (expected `"// &
2788                  apt2str(this%ptype)//"' got LOGICAL)",-21)
2789    ELSEIF (words_length(this%values) == 0) THEN
2790      ALLOCATE(output(MAX(this%nrec,1)))
2791      ok = from_string(this%default,output(1))
2792      output(1:SIZE(output)) = output(1)
2793    ELSE
2794      IF (ALLOCATED(output)) DEALLOCATE(output)
2795      ALLOCATE(output(words_length(this%values)))
2796      ok = words_to_vector(this%values,tmp)
2797      ok = from_string(tmp, output)
2798    ENDIF
2799  END FUNCTION ac_get_lv_ve
2800
2801  FUNCTION ac_get_cv_ve(this, output) RESULT(ret)
2802    !! Get a vector of `COMPLEX` values from given argument
2803    !! If no error occured, the function always returns at least a value (whatever the parser's
2804    !! state is) which is the default value if no specific values are set in the argument.
2805    !! Otherwise, `output` status is undefined.
2806    TYPE(argc), INTENT(in)                          :: this
2807      !! Argc object
2808    COMPLEX, INTENT(out), ALLOCATABLE, DIMENSION(:) :: output
2809      !! Output values
2810    TYPE(error) :: ret
2811      !! Error object with the first error encountered in the process
2812    CHARACTER(len=st_slen), ALLOCATABLE, DIMENSION(:) :: tmp
2813    LOGICAL                                           :: ok
2814    ret = noerror
2815    IF (this%ptype /= ap_complex) THEN
2816      ret = error("argparse: invalid type for output (expected `"// &
2817                  apt2str(this%ptype)//"' got COMPLEX)",-21)
2818    ELSEIF (words_length(this%values) == 0) THEN
2819      ALLOCATE(output(MAX(this%nrec,1)))
2820      ok = from_string(this%default,output(1))
2821      output(1:SIZE(output)) = output(1)
2822    ELSE
2823      IF (ALLOCATED(output)) DEALLOCATE(output)
2824      ALLOCATE(output(words_length(this%values)))
2825      ok = words_to_vector(this%values,tmp)
2826      ok = from_string(tmp, output)
2827    ENDIF
2828  END FUNCTION ac_get_cv_ve
2829
2830  FUNCTION ac_get_sv_ve(this, output) RESULT(ret)
2831    !! Get a vector of `STRING` values from given argument
2832    !! If no error occured, the function always returns at least a value (whatever the parser's
2833    !! state is) which is the default value if no specific values are set in the argument.
2834    !! Otherwise, `output` status is undefined.
2835    TYPE(argc), INTENT(in)                                         :: this
2836      !! Argc object
2837    CHARACTER(len=st_slen), INTENT(out), ALLOCATABLE, DIMENSION(:) :: output
2838      !! Output values
2839    TYPE(error) :: ret
2840      !! Error object with the first error encountered in the process
2841    ret = noerror
2842    IF (this%ptype /= ap_string) THEN
2843      ret = error("argparse: invalid type for output (expected `"// &
2844                  apt2str(this%ptype)//"' got STRING)",-21)
2845    ELSEIF (words_length(this%values) == 0) THEN
2846      ALLOCATE(output(MAX(this%nrec,1)))
2847      output(1:SIZE(output)) = TRIM(this%default)
2848    ELSE
2849      IF (.NOT.words_to_vector(this%values,output)) DEALLOCATE(output)
2850    ENDIF
2851  END FUNCTION ac_get_sv_ve
2852
2853  ! miscellaneous methods
2854  ! ---------------------
2855
2856  FUNCTION apt2str(ap_t) RESULT(str)
2857    !! Get the string representation of argparse types constants
2858    INTEGER, INTENT(in) :: ap_t
2859      !! One of ap_logical, ap_integer, ap_real, ap_complex or ap_string module constants.
2860    CHARACTER(len=:), ALLOCATABLE :: str
2861      !! String representation of the type.
2862    SELECT CASE(ap_t)
2863      CASE(ap_logical) ; str = 'logical'
2864      CASE(ap_integer) ; str = 'integer'
2865      CASE(ap_real)    ; str = 'real'
2866      CASE(ap_complex) ; str = 'complex'
2867      CASE(ap_string)  ; str = 'string'
2868      CASE DEFAULT     ; str = 'unknown'
2869    END SELECT
2870    RETURN
2871  END FUNCTION apt2str
2872
2873  FUNCTION apa2str(ap_a) RESULT(str)
2874    !! Get the string representation of argparse actions constants
2875    INTEGER, INTENT(in) :: ap_a
2876     !! One of ap_store, ap_append,cap_count or ap_help module constants
2877    CHARACTER(len=:), ALLOCATABLE :: str
2878      !! String representation of the action.
2879    SELECT CASE(ap_a)
2880      CASE(ap_store)  ; str = 'store'
2881      CASE(ap_append) ; str = 'append'
2882      CASE(ap_count)  ; str = 'count'
2883      CASE(ap_help)   ; str = 'help'
2884      CASE DEFAULT    ; str = 'unknown'
2885    END SELECT
2886    RETURN
2887  END FUNCTION apa2str
2888
2889  FUNCTION get_progname() RESULT(name)
2890    !> Get the name of the program
2891    CHARACTER(len=:), ALLOCATABLE :: name !! The name of the program
2892    INTEGER :: c
2893    CALL GET_COMMAND_ARGUMENT(0,length=c)
2894    ALLOCATE(CHARACTER(len=c) :: name)
2895    CALL GET_COMMAND_ARGUMENT(0,value=name)
2896    c = INDEX(name, "/", back=.true.)
2897    IF (c /= 0.AND.c /= LEN_TRIM(name)) name = TRIM(name(c+1:))
2898  END FUNCTION get_progname
2899
2900END MODULE ARGPARSE
2901
Note: See TracBrowser for help on using the repository browser.