TABLE OF CONTENTS


ABINIT/m_argparse [ Modules ]

[ Top ] [ Modules ]

NAME

 m_argparse

FUNCTION

   Simple argument parser used in main programs

COPYRIGHT

  Copyright (C) 2008-2024 ABINIT group (MG)
  This file is distributed under the terms of the
  GNU General Public License, see ~abinit/COPYING
  or http://www.gnu.org/copyleft/gpl.txt .

SOURCE

16 #if defined HAVE_CONFIG_H
17 #include "config.h"
18 #endif
19 
20 #include "abi_common.h"
21 
22 module m_argparse
23 
24  use defs_basis
25  use m_abicore
26  use m_errors
27  use m_xmpi
28  use m_xomp
29  use m_xieee
30  use m_abi_linalg
31  use m_fft
32  use m_exit
33  use m_clib
34  use m_nctk
35 
36  use m_build_info,      only : dump_config, abinit_version
37  use m_io_tools,        only : open_file, file_exists, enforce_fortran_io
38  use m_cppopts_dumper,  only : dump_cpp_options
39  use m_optim_dumper,    only : dump_optim
40  use m_fstrings,        only : atoi, atof, itoa, firstchar, startswith, endswith, sjoin, find_and_select
41  use m_time,            only : str2sec
42  use m_libpaw_tools,    only : libpaw_log_flag_set
43  use m_ipi,             only : ipi_setup
44 
45  implicit none
46 
47  private
48 
49  public :: get_arg         !  Parse scalar argument from command line. Return exit code.
50 
51  interface get_arg
52    module procedure get_arg_int
53    module procedure get_arg_dp
54    module procedure get_arg_str
55    module procedure get_arg_bool
56  end interface get_arg
57 
58  public :: get_arg_list    ! Parse array argument from command line. Return exit code.
59 
60  interface get_arg_list
61    module procedure get_arg_list_int
62    module procedure get_arg_list_dp
63  end interface get_arg_list
64 
65  public :: get_start_step_num    ! Parse string from command line in the format "start:step:num"
66                                  ! defining an arithmetic progression.
67  public :: parse_kargs           !  Parse command line arguments, return options related to k-point sampling

ABINIT/parse_kargs [ Functions ]

[ Top ] [ Functions ]

NAME

 parse_kargs

FUNCTION

  Parse command line arguments, return options related to k-point sampling

INPUTS

OUTPUT

SOURCE

 985 subroutine parse_kargs(kptopt, kptrlatt, nshiftk, shiftk, chksymbreak)
 986 
 987 !Arguments ------------------------------------
 988  integer,intent(out) :: kptopt, nshiftk, chksymbreak
 989  integer,intent(out) :: kptrlatt(3,3)
 990  real(dp),allocatable,intent(out) :: shiftk(:,:)
 991 
 992 !Local variables-------------------------------
 993  integer :: ii, lenr, ierr
 994  character(len=500) :: msg
 995  integer :: ivec9(9), ngkpt(3)
 996  real(dp) :: my_shiftk(3 * MAX_NSHIFTK)
 997 
 998 ! *************************************************************************
 999 
1000  ABI_CHECK(get_arg("kptopt", kptopt, msg, default=1) == 0, msg)
1001  ABI_CHECK(get_arg("chksymbreak", chksymbreak, msg, default=1) == 0, msg)
1002 
1003  ierr = get_arg_list("ngkpt", ngkpt, lenr, msg, exclude="kptrlatt", want_len=3)
1004  if (ierr == 0) then
1005  !if (lenr == 3) then
1006    kptrlatt = 0
1007    do ii=1,3
1008      kptrlatt(ii, ii) = ngkpt(ii)
1009    end do
1010  else
1011    ABI_CHECK(get_arg_list("kptrlatt", ivec9, lenr, msg, exclude="ngkpt", want_len=9) == 0, msg)
1012    ABI_CHECK(lenr == 9, "Expecting 9 values for kptrlatt")
1013    kptrlatt = transpose(reshape(ivec9, [3, 3]))
1014  end if
1015 
1016  ! Init default
1017  ABI_CHECK(get_arg_list("shiftk", my_shiftk, lenr, msg) == 0, msg)
1018  if (lenr /= 0) then
1019    ABI_CHECK(mod(lenr, 3) == 0, "Expecting 3 * nshift array")
1020    nshiftk = lenr / 3
1021    ABI_MALLOC(shiftk, (3, nshiftk))
1022    shiftk = reshape(my_shiftk(1:lenr), [3, nshiftk])
1023  else
1024    nshiftk = 1
1025    ABI_CALLOC(shiftk, (3, nshiftk))
1026    !shiftk(:, 1) = [half, half, half]
1027  end if
1028  !write(std_out, *)"kptopt = ", kptopt, ", chksymbreak = ", chksymbreak, ", nshiftk = ", nshiftk, ", kptrlatt = ", kptrlatt
1029 
1030 end subroutine parse_kargs

m_argparse/args_parser [ Functions ]

[ Top ] [ m_argparse ] [ Functions ]

NAME

  args_parser

FUNCTION

  Simple command line argument parser for abinit and other main programs.

SOURCE

122 type(args_t) function args_parser() result(args)
123 
124 !Local variables-------------------------------
125  integer :: ii, ierr, ntasks_per_node = -1
126  logical :: iam_master, verbose
127  real(dp) :: timelimit, memb_per_node = -one, memb_per_cpu = -one
128  character(len=500) :: arg !,msg
129 
130 ! *************************************************************************
131 
132  args%exit = 0; ierr=0; verbose = .False.
133 
134 #ifndef HAVE_FC_COMMAND_ARGUMENT
135  call wrtout(std_out,"get_command_argument is not supported by FC. Ignoring command lines options!")
136  return ! Nothing to do
137 #else
138 
139  if (command_argument_count() == 0) return
140 
141  iam_master = xmpi_comm_rank(xmpi_world) == 0
142 
143  ! Store full command line for future reference.
144  call get_command(args%cmdline)
145 
146  do ii=1,command_argument_count()
147    call get_command_argument(ii, arg)
148    !write(std_out,*)"arg", trim(arg)
149 
150    if (ii == 1 .and. .not. firstchar(arg, "-")) then
151      ! `abinit path` syntax reads input from path and deactivates files file mode.
152      args%input_path = trim(arg)
153      if (iam_master) then
154         ABI_CHECK(file_exists(args%input_path), sjoin("Cannot find input file:", args%input_path))
155      end if
156      cycle
157    end if
158 
159    if (arg == "-v" .or. arg == "--version") then
160      call wrtout(std_out, trim(abinit_version))
161      args%exit = args%exit + 1
162 
163    else if (arg == "-b" .or. arg == "--build") then
164      call print_kinds(unit=std_out)
165      call xmpi_show_info(unit=std_out)
166      call dump_cpp_options(std_out)
167      call dump_config(std_out)
168      call dump_optim(std_out)
169 
170      args%exit = args%exit + 1
171 
172    else if (arg == "-d" .or. arg == "--dry-run") then
173      args%dry_run = 1
174 
175    else if (arg == "--abimem-level") then
176      call get_command_argument(ii + 1, arg)
177      args%abimem_level = atoi(arg)
178 
179    else if (arg == "--abimem-limit-mb") then
180      call get_command_argument(ii + 1, arg)
181      args%abimem_limit_mb = atof(arg)
182 
183    else if (arg == "-j" .or. arg == "--omp-num-threads") then
184      call get_command_argument(ii + 1, arg)
185      call xomp_set_num_threads(atoi(arg))
186 
187    else if (arg == "-t" .or. arg == "--timelimit") then
188      ! timelimit handler.
189      call get_command_argument(ii + 1, arg)
190      timelimit = str2sec(arg)
191      if (timelimit < zero) then
192        write(std_out,*)"Wrong timelimit argument: ",trim(arg)
193        args%exit = args%exit + 1
194      else
195        call exit_init(timelimit)
196      end if
197 
198    else if (arg == "--ieee-halt") then
199      ! IEEE exceptions.
200      call xieee_halt_ifexc(.True.)
201 
202    else if (arg == "--ieee-signal") then
203      call xieee_signal_ifexc(.True.)
204 
205    else if (begins_with(arg, "--fft-ialltoall")) then
206      ! Enable/disable non-blocking ialltoall in MPI-FFT
207      call fft_allow_ialltoall(parse_yesno(arg, "--fft-ialltoall"))
208 
209    else if (begins_with(arg, "--ipi")) then
210      call get_command_argument(ii + 1, arg)
211      call ipi_setup(arg, xmpi_world)
212 
213    else if (begins_with(arg, "--use-xgemm3m")) then
214      ! Enable/disable [Z,C]GEMM3
215      call linalg_allow_gemm3m(parse_yesno(arg, "--use-xgemm3m"), write_msg=iam_master)
216 
217    else if (begins_with(arg, "--use-mpi-in-place")) then
218      ! Enable/disable usage of MPI_IN_PLACE.
219      call xmpi_set_inplace_operations(parse_yesno(arg, "--use-mpi-in-place"))
220 
221    else if (begins_with(arg, "--plasma")) then
222      ! Enable/disable PLASMA
223      call linalg_allow_plasma(parse_yesno(arg, "--plasma"))
224 
225    else if (arg == "--gnu-mtrace") then
226      if (iam_master) then
227        call clib_mtrace(ierr)
228        ABI_CHECK(ierr == 0, sjoin("clib_mtrace returned ierr:", itoa(ierr)))
229      end if
230 
231    else if (arg == "--log") then
232      ! Enable logging
233      call abi_log_status_state(new_do_write_log=.True., new_do_write_status=.True.)
234      call libpaw_log_flag_set(.True.)
235 
236    else if (arg == "--netcdf-classic") then
237      ! Use netcdf classic mode for new files when only sequential-IO needs to be performed
238      call nctk_use_classic_for_seq()
239 
240    else if (arg == "--enforce-fortran-io") then
241      call enforce_fortran_io(.True.)
242 
243    else if (begins_with(arg, "--mem-per-cpu=")) then
244      memb_per_cpu = parse_slurm_mem(arg, "--mem-per-cpu=")
245      call set_mem_per_cpu_mb(memb_per_cpu)
246 
247    else if (begins_with(arg, "--mem=")) then
248      memb_per_node = parse_slurm_mem(arg, "--mem=")
249 
250    else if (begins_with(arg, "--ntasks-per-node=")) then
251      call get_command_argument(ii + 1, arg)
252      ntasks_per_node = atoi(arg)
253 
254    else if (arg == "--F03") then
255      ! For multibinit only
256      args%multibinit_F03_mode = 1
257 
258    else if (arg == "-h" .or. arg == "--help") then
259      if (iam_master) then
260        ! Document the options.
261        write(std_out,*)"-v, --version              Show version number and exit."
262        write(std_out,*)"-b, --build                Show build parameters and exit."
263        write(std_out,*)"-d, --dry-run              Validate input file and exit."
264        write(std_out,*)"-j, --omp-num-threads      Set the number of OpenMp threads."
265        write(std_out,*)"--use-xgemm3m[=yesno]      Use ZGEMM3M routines instead of ZGEMM. Default: no "
266        write(std_out,*)"--use-mpi-in-place[=yesno] Enable/disable usage of MPI_IN_PLACE in e.g. xmpi_sum. Default: no"
267        write(std_out,*)"                           Note that some MPI libs e.g. intel-mpi may not implement this feature"
268        write(std_out,*)"                           correctly so it is adviced to test this option with e.g. structural"
269        write(std_out,*)"                           relaxations before running production calculations."
270        write(std_out,*)"--ipi                      Activate socket-driven calculation using i-pi protocol."
271        write(std_out,*)"                           For UNIX socket, use: --ipi {unixsocket}:UNIX"
272        write(std_out,*)"                           For INET socket, use  --ipi {host}:{port}. Usage example:"
273        write(std_out,*)"                           `abinit run.abi --ipi {unixsocket}:UNIX > run.log`"
274        write(std_out,*)"                           NB: Requires ionmov 28 and some tuning of input variables. See:"
275        write(std_out,*)"                           https://wiki.fysik.dtu.dk/ase/dev/ase/calculators/socketio/socketio.html"
276        write(std_out,*)"--log                      Enable log files and status files in parallel execution."
277        write(std_out,*)"--netcdf-classic           Use netcdf classic mode for new files if parallel-IO is not needed."
278        write(std_out,*)"                           Default is netcdf4/hdf5"
279        write(std_out,*)"--enforce-fortran-io       Use Fortran-IO instead of MPI-IO when operating on Fortran files"
280        write(std_out,*)"                           Useful to read files when the MPI-IO library is not efficient."
281        write(std_out,*)"                           DON'T USE this option when the code needs to write large files e.g. WFK"
282        write(std_out,*)"-t, --timelimit            Set the timelimit for the run. Accepts time in Slurm syntax:"
283        write(std_out,*)"                               days-hours"
284        write(std_out,*)"                               days-hours:minutes"
285        write(std_out,*)"                               days-hours:minutes:seconds"
286        write(std_out,*)"                               minutes"
287        write(std_out,*)"                               minutes:seconds"
288        write(std_out,*)"                               hours:minutes:seconds"
289        write(std_out,*)"                           At present only GS, relaxations and MD runs support this option"
290        write(std_out,*)"--mem-per-cpu=<size>[units] Set memory per cpu using Slurm syntax. Default units are megabytes."
291        write(std_out,*)"                           Different units can be specified using the suffix [K|M|G|T]."
292        write(std_out,*)"--mem=<size>[units]        Set memory per node using Slurm syntax. Default units are megabytes."
293        write(std_out,*)"                           Requires `ntasks-per-node`. Not compatibile with `-mem-per-cpu`."
294        write(std_out,*)"--ntasks-per-node=INT      Set number of tasks per node. Used in conjunction with --mem`"
295        write(std_out,*)"--verbose                  Enable verbose mode in argparse"
296        write(std_out,*)"-h, --help                 Show this help and exit."
297 
298        write(std_out,*)""
299        write(std_out,*)""
300        write(std_out,*)"=============================="
301        write(std_out,*)"=== Options for developers ==="
302        write(std_out,*)"=============================="
303        write(std_out,*)"--abimem-level NUM         Set memory profiling level. Requires HAVE_MEM_PROFILING"
304        write(std_out,*)"--abimem-limit-mb NUM      Log malloc/free only if size > limit in Megabytes. Requires abimem-level 3"
305        write(std_out,*)"--fft-ialltoall[=yesno]    Use non-blocking ialltoall in MPI-FFT (used only if ndat > 1 and MPI2+)."
306        write(std_out,*)"--gnu-mtrace               Enable mtrace (requires GNU and clib)."
307        write(std_out,*)"--ieee-halt                Halt the code if one of the *usual* IEEE exceptions is raised."
308        write(std_out,*)"--ieee-signal              Signal the occurrence of the *usual* IEEE exceptions."
309        ! Multibinit
310        write(std_out,*)"--F03                      Run F03 mode (for Multibinit only)."
311      end if
312      args%exit = args%exit + 1
313 
314    else if (arg == "--verbose") then
315      verbose = .True.
316 
317    else
318      if (firstchar(arg, "-")) then
319        ABI_WARNING("Unsupported option: "//trim(arg))
320        args%exit = args%exit + 1
321      else
322        continue
323      end if
324    end if
325  end do
326 
327  if (ntasks_per_node /= -1 .or. memb_per_node /= -one) then
328    ! Set mem_per_cpu from node info.
329    ABI_CHECK(ntasks_per_node /= -1, "`mem-per-node` requires `ntasks-per-node`")
330    ABI_CHECK(memb_per_node /= -one, "`ntasks-per-node` requires `mem-per-node`")
331    ABI_CHECK(memb_per_cpu == -one, "`mem-per-cpu` and `mem-per-node` are mutually exclusive!")
332    call set_mem_per_cpu_mb(memb_per_node / ntasks_per_node)
333  end if
334 
335 #endif
336 
337 end function args_parser

m_argparse/args_t [ Types ]

[ Top ] [ m_argparse ] [ Types ]

NAME

 args_t

FUNCTION

 Stores command line options

SOURCE

 79  type,public :: args_t
 80 
 81    integer :: exit = 0
 82     ! /=0 to exit after having parsed the command line options.
 83 
 84    integer :: abimem_level = 0
 85     ! Options for memory profiling. See m_profiling_abi
 86 
 87    integer :: dry_run = 0
 88     ! /= 0 to exit after the validation of the input file.
 89 
 90    real(dp) :: abimem_limit_mb = 20.0_dp
 91     ! Optional memory limit in Mb. used when abimem_level == 3
 92 
 93    character(len=500) :: cmdline = ""
 94     ! The entire command line
 95 
 96    character(len=fnlen) :: input_path = ""
 97 
 98    !! Below are for multibinit
 99    integer :: multibinit_F03_mode = 0
100    !1: legacy mode
101    !0: use full F03 implementation mode
102    ! TODO: It will be deprecated when everything is ready in and the new mode will be default.
103 
104  end type args_t
105 
106  public :: args_parser   ! Parse command line options.

m_argparse/begins_with [ Functions ]

[ Top ] [ m_argparse ] [ Functions ]

NAME

  begins_with

FUNCTION

  Returns true if argument arg begins with string

SOURCE

349 pure logical function begins_with(arg, string) result(bool)
350 
351 !Arguments ------------------------------------
352  character(len=*),intent(in) :: arg,string
353 ! *************************************************************************
354 
355  bool = .False.; if (len(arg) >= len(string)) bool = (arg(1:len(string)) == string)
356 
357 end function begins_with

m_argparse/get_arg_bool [ Functions ]

[ Top ] [ m_argparse ] [ Functions ]

NAME

  get_arg_bool

FUNCTION

  Parse scalar boolean argument from command line. Return exit code.

INPUTS

  argname= Argument name
  [default]= Default value
  [exclude]= argname and exclude are mutually exclusive.

OUTPUT

   argval= Value of argname
   msg= Error message

SOURCE

657 integer function get_arg_bool(argname, argval, msg, default, exclude) result(ierr)
658 
659 !Arguments ------------------------------------
660 !scalars
661  character(len=*),intent(in) :: argname
662  logical,intent(out) :: argval
663  character(len=*),intent(out) :: msg
664  logical,optional,intent(in) :: default
665  character(len=*),optional,intent(in) :: exclude
666 
667 !Local variables-------------------------------
668  integer :: ii
669  logical :: found_argname, found_excl
670  character(len=500) :: arg
671 
672 ! *************************************************************************
673 
674  ierr = 0; msg = ""; if (present(default)) argval = default
675  found_argname = .False.; found_excl = .False.
676  argval = .False.
677 
678  do ii=1,command_argument_count()
679    call get_command_argument(ii, arg)
680    if (present(exclude)) then
681      if (arg == "--" // trim(exclude)) found_excl = .True.
682    end if
683    if (begins_with(arg, "--" // trim(argname))) then
684      argval = parse_yesno(arg, "--" // trim(argname), default=.True.)
685      found_argname = .True.
686    end if
687  end do
688 
689  if (ierr /= 0) msg = sjoin("Error while reading argument: ", argname, ch10, msg)
690  if (found_argname .and. found_excl) then
691    ierr = ierr + 1; msg = sjoin("Variables", argname, "and", exclude, "are mutually exclusive", ch10, msg)
692  end if
693 
694 end function get_arg_bool

m_argparse/get_arg_dp [ Functions ]

[ Top ] [ m_argparse ] [ Functions ]

NAME

  get_arg_dp

FUNCTION

  Parse scalar argument from command line. Return exit code.

INPUTS

  argname= Argument name
  [default]= Default value
  [exclude]= argname and exclude are mutually exclusive.

OUTPUT

   argval= Value of argname
   msg= Error message

SOURCE

529 integer function get_arg_dp(argname, argval, msg, default, exclude) result(ierr)
530 
531 !Arguments ------------------------------------
532 !scalars
533  character(len=*),intent(in) :: argname
534  real(dp),intent(out) :: argval
535  character(len=*),intent(out) :: msg
536  real(dp),optional,intent(in) :: default
537  character(len=*),optional,intent(in) :: exclude
538 
539 !Local variables-------------------------------
540  integer :: ii, istat
541  logical :: found_argname, found_excl
542  character(len=500) :: arg, iomsg
543 
544 ! *************************************************************************
545 
546  ierr = 0; msg = ""; if (present(default)) argval = default
547  found_argname = .False.; found_excl = .False.
548 
549  do ii=1,command_argument_count()
550    call get_command_argument(ii, arg)
551    if (present(exclude)) then
552      if (arg == "--" // trim(exclude)) found_excl = .True.
553    end if
554    if (arg == "--" // trim(argname)) then
555      found_argname = .True.
556      call get_command_argument(ii + 1, arg, status=istat)
557      if (istat == 0) then
558        read(arg, *, iostat=istat, iomsg=iomsg) argval
559        if (istat /= 0) then
560          ierr = ierr + 1; msg = sjoin(msg, ch10, iomsg)
561        end if
562      else
563        ierr = ierr + 1; msg = sjoin(msg, ch10, "Error in get_command_argument")
564      end if
565    end if
566  end do
567 
568  if (ierr /= 0) msg = sjoin("Error while reading argument: ", argname, ch10, msg)
569  if (found_argname .and. found_excl) then
570    ierr = ierr + 1; msg = sjoin("Variables", argname, "and", exclude, "are mutually exclusive", ch10, msg)
571  end if
572 
573 end function get_arg_dp

m_argparse/get_arg_int [ Functions ]

[ Top ] [ m_argparse ] [ Functions ]

NAME

  get_arg_int

FUNCTION

  Parse scalar argument from command line. Return exit code.

 INPUT
  argname= Argument name
  [default]= Default value.
  [exclude]= argname and exclude are mutually exclusive.

OUTPUT

  argval= Value of argname
  msg= Error message

SOURCE

464 integer function get_arg_int(argname, argval, msg, default, exclude) result(ierr)
465 
466 !Arguments ------------------------------------
467 !scalars
468  character(len=*),intent(in) :: argname
469  integer,intent(out) :: argval
470  character(len=*),intent(out) :: msg
471  integer,optional,intent(in) :: default
472  character(len=*),optional,intent(in) :: exclude
473 
474 !Local variables-------------------------------
475  integer :: ii, istat
476  logical :: found_argname, found_excl
477  character(len=500) :: arg, iomsg
478 
479 ! *************************************************************************
480 
481  ierr = 0; msg = ""; if (present(default)) argval = default
482  found_argname = .False.; found_excl = .False.
483 
484  do ii=1,command_argument_count()
485    call get_command_argument(ii, arg)
486    if (present(exclude)) then
487      if (arg == "--" // trim(exclude)) found_excl = .True.
488    end if
489    if (arg == "--" // trim(argname)) then
490      found_argname = .True.
491      call get_command_argument(ii + 1, arg, status=istat)
492      if (istat == 0) then
493        read(arg, *, iostat=istat, iomsg=iomsg) argval
494        if (istat /= 0) then
495          ierr = ierr + 1; msg = sjoin(msg, ch10, iomsg)
496        end if
497      else
498        ierr = ierr + 1; msg = sjoin(msg, ch10, "Error in get_command_argument")
499      end if
500    end if
501  end do
502 
503  if (ierr /= 0) msg = sjoin("Error while reading argument: ", argname, ch10, msg)
504  if (found_argname .and. found_excl) then
505    ierr = ierr + 1; msg = sjoin("Variables", argname, "and", exclude, "are mutually exclusive", ch10, msg)
506  end if
507 
508 end function get_arg_int

m_argparse/get_arg_list_dp [ Functions ]

[ Top ] [ m_argparse ] [ Functions ]

NAME

  get_arg_list_dp

FUNCTION

 INPUT
  argname
  [default]
  [default_list]
  [exclude]
  [want_len]

OUTPUT

  argval
  msg

SOURCE

891 integer function get_arg_list_dp(argname, argval, lenr, msg, default, default_list, exclude, want_len) result(ierr)
892 
893 !Arguments ------------------------------------
894 !scalars
895  character(len=*),intent(in) :: argname
896  real(dp),intent(out) :: argval(:)
897  integer,intent(out) :: lenr
898  character(len=*),intent(out) :: msg
899  character(len=*),optional,intent(in) :: exclude
900  real(dp),optional,intent(in) :: default
901  real(dp),optional,intent(in) :: default_list(:)
902  integer,optional,intent(in) :: want_len
903 
904 !Local variables-------------------------------
905  integer :: ii, istat, iarg, maxlen
906  logical :: found_argname, found_excl
907  character(len=500) :: arg, iomsg
908 
909 ! *************************************************************************
910 
911  ierr = 0; msg = ""; lenr = 0
912  found_argname = .False.; found_excl = .False.
913 
914  maxlen = size(argval);
915  if (maxlen == 0) then
916    ierr = ierr + 1; msg = "zero-sized argval!"; return
917  end if
918 
919  if (present(default)) argval = default
920  if (present(default_list)) argval = default_list
921 
922  do ii=1,command_argument_count()
923    call get_command_argument(ii, arg)
924    if (present(exclude)) then
925      if (arg == "--" // trim(exclude)) found_excl = .True.
926    end if
927    if (arg == "--" // trim(argname)) then
928      ! Read list of values
929      found_argname = .True.
930      do iarg=1,maxlen
931        call get_command_argument(ii + iarg, arg, status=istat)
932        if (istat == 0) then
933          !write(std_out, *)"arg:", trim(arg)
934          if (startswith(arg, "--")) exit
935          read(arg,*, iostat=istat, iomsg=iomsg) argval(iarg)
936          if (istat == 0) then
937            lenr = lenr + 1
938          else
939            ierr = ierr + 1; msg = sjoin(msg, ch10, iomsg)
940          end if
941        else
942          ! If there are less than NUMBER arguments specified at the command line, VALUE will be filled with blanks.
943          if (arg == "") exit
944          ierr = ierr + 1; msg = sjoin(msg, ch10, "Error in get_command_argument")
945        end if
946      end do
947    end if
948  end do
949 
950  if (ierr /= 0) msg = sjoin("Error while reading argument: ", argname, ch10, msg)
951  if (found_argname .and. found_excl) then
952    ierr = ierr + 1; msg = sjoin("Variables", argname, "and", exclude, "are mutually exclusive", ch10, msg)
953  end if
954 
955  if (present(want_len)) then
956    if (found_argname) then
957      if (want_len /= lenr) then
958        ierr = ierr + 1
959        msg = sjoin(argname, "requires", itoa(want_len), " tokens while found ", itoa(lenr), ch10, msg)
960      end if
961    else
962      ierr = ierr + 1
963      msg = sjoin("Cannot find --", argname, " option in CLI and want_len:", itoa(want_len), ch10, msg)
964    end if
965  end if
966 
967 end function get_arg_list_dp

m_argparse/get_arg_list_int [ Functions ]

[ Top ] [ m_argparse ] [ Functions ]

NAME

  get_arg_list_int

FUNCTION

  Parse array argument from command line. Return exit code.

 INPUT
  argname= Argument name
  [default]= Default value (scalar)
  [default_list]= Default value (vector)
  [exclude]= argname and exclude are mutually exclusive.
  [want_len]= Require want_len items in CLI.

OUTPUT

  argval= Value of argname
  msg= Error message

SOURCE

791 integer function get_arg_list_int(argname, argval, lenr, msg, default, default_list, exclude, want_len) result(ierr)
792 
793 !Arguments ------------------------------------
794 !scalars
795  character(len=*),intent(in) :: argname
796  integer,intent(out) :: argval(:)
797  integer,intent(out) :: lenr
798  character(len=*),intent(out) :: msg
799  character(len=*),optional,intent(in) :: exclude
800  integer,optional,intent(in) :: default
801  integer,optional,intent(in) :: default_list(:)
802  integer,optional,intent(in) :: want_len
803 
804 !Local variables-------------------------------
805  integer :: ii, istat, iarg, maxlen
806  logical :: found_argname, found_excl
807  character(len=500) :: arg, iomsg
808 
809 ! *************************************************************************
810 
811  ierr = 0; msg = ""; lenr = 0
812  found_argname = .False.; found_excl = .False.
813 
814  maxlen = size(argval);
815  if (maxlen == 0) then
816    ierr = ierr + 1; msg = "zero-sized argval!"; return
817  end if
818 
819  if (present(default)) argval = default
820  if (present(default_list)) argval = default_list
821 
822  do ii=1,command_argument_count()
823    call get_command_argument(ii, arg)
824    if (present(exclude)) then
825      if (arg == "--" // trim(exclude)) found_excl = .True.
826    end if
827    if (arg == "--" // trim(argname)) then
828      ! Read list of values
829      found_argname = .True.
830      do iarg=1,maxlen
831        call get_command_argument(ii + iarg, arg, status=istat)
832        if (istat == 0) then
833          !write(std_out, *)"arg:", trim(arg)
834          if (startswith(arg, "--")) exit
835          read(arg,*, iostat=istat, iomsg=iomsg) argval(iarg)
836          if (istat == 0) then
837            lenr = lenr + 1
838          else
839            ierr = ierr + 1; msg = sjoin(msg, ch10, iomsg)
840          end if
841        else
842          ! If there are less than NUMBER arguments specified at the command line, VALUE will be filled with blanks.
843          if (arg == "") exit
844          ierr = ierr + 1; msg = sjoin(msg, ch10, "Error in get_command_argument")
845        end if
846      end do
847    end if
848  end do
849 
850  if (ierr /= 0) msg = sjoin("Error while reading argument: ", argname, ch10, msg)
851  if (found_argname .and. found_excl) then
852    ierr = ierr + 1; msg = sjoin("Variables", argname, "and", exclude, "are mutually exclusive", ch10, msg)
853  end if
854 
855  if (present(want_len)) then
856    if (found_argname) then
857      if (want_len /= lenr) then
858        ierr = ierr + 1
859        msg = sjoin(argname, "requires", itoa(want_len), " tokens while found ", itoa(lenr), ch10, msg)
860      end if
861    else
862      ierr = ierr + 1
863      msg = sjoin("Cannot find --", argname, "option in CLI and want_len:", itoa(want_len), ch10, msg)
864    end if
865  end if
866 
867 end function get_arg_list_int

m_argparse/get_arg_str [ Functions ]

[ Top ] [ m_argparse ] [ Functions ]

NAME

  get_arg_str

FUNCTION

  Parse scalar string argument from command line. Return exit code.

INPUTS

  argname= Argument name
  [default]= Default value
  [exclude]= argname and exclude are mutually exclusive.

OUTPUT

   argval= Value of argname
   msg= Error message

SOURCE

596 integer function get_arg_str(argname, argval, msg, default, exclude) result(ierr)
597 
598 !Arguments ------------------------------------
599 !scalars
600  character(len=*),intent(in) :: argname
601  character(len=*),intent(out) :: argval, msg
602  character(len=*),optional,intent(in) :: default
603  character(len=*),optional,intent(in) :: exclude
604 
605 !Local variables-------------------------------
606  integer :: ii, istat
607  logical :: found_argname, found_excl
608  character(len=500) :: arg
609 
610 ! *************************************************************************
611 
612  ierr = 0; msg = ""; if (present(default)) argval = default
613  found_argname = .False.; found_excl = .False.
614 
615  do ii=1,command_argument_count()
616    call get_command_argument(ii, arg)
617    if (present(exclude)) then
618      if (arg == "--" // trim(exclude)) found_excl = .True.
619    end if
620    if (arg == "--" // trim(argname)) then
621      found_argname = .True.
622      call get_command_argument(ii + 1, argval, status=istat)
623      if (istat /= 0) then
624        ierr = ierr + 1; msg = sjoin(msg, ch10, "Error in get_command_argument")
625      end if
626    end if
627  end do
628 
629  if (ierr /= 0) msg = sjoin("Error while reading argument: ", argname, ch10, msg)
630  if (found_argname .and. found_excl) then
631    ierr = ierr + 1; msg = sjoin("Variables", argname, "and", exclude, "are mutually exclusive", ch10, msg)
632  end if
633 
634 end function get_arg_str

m_argparse/get_start_step_num [ Functions ]

[ Top ] [ m_argparse ] [ Functions ]

NAME

  get_start_step_num

FUNCTION

  Parse string from command line in the format "start:step:num" defining an arithmetic progression.
  Return exit code.

INPUTS

  argname= Argument name
  [default]= Default value
  [exclude]= argname and exclude are mutually exclusive.

OUTPUT

   ilist= [start, step, num]
   msg= Error message

SOURCE

718 integer function get_start_step_num(argname, ilist, msg, default, exclude) result(ierr)
719 
720 !Arguments ------------------------------------
721 !scalars
722  character(len=*),intent(in) :: argname
723  integer,intent(out) :: ilist(3)
724  character(len=*),intent(out) :: msg
725  integer,optional,intent(in) :: default(3)
726  character(len=*),optional,intent(in) :: exclude
727 
728 !Local variables-------------------------------
729  integer :: ii, jj
730  character(len=500) :: str
731 
732 ! *************************************************************************
733 
734  if (present(exclude)) then
735    ierr = get_arg_str(argname, str, msg, default="", exclude=exclude)
736  else
737    ierr = get_arg_str(argname, str, msg, default="")
738  end if
739  if (ierr /= 0) return
740 
741  if (len_trim(str) == 0) then
742    if (present(default)) then
743      ilist = default
744    else
745      ierr = ierr + 1; msg = sjoin("Variables", argname, "is not found and default is not given")
746    end if
747    return
748  end if
749 
750  ! We got a non-empty string. Let's parse it.
751  ii = index(str, ":")
752  if (ii <= 1) then
753    msg = sjoin("Cannot find first `:` in string:", str)
754    ierr = ierr + 1; return
755  end if
756  ilist(1) = atoi(str(1:ii-1))
757 
758  jj = index(str(ii+1:), ":")
759  if (jj == 0) then
760    msg = sjoin("Cannot find second `:` in string:", str)
761    ierr = ierr + 1; return
762  end if
763 
764  ilist(2) = atoi(str(ii+1: jj+ii-1))
765  ilist(3) = atoi(str(jj+ii+1:))
766  !print *, "ilist:", ilist
767 
768 end function get_start_step_num

m_argparse/parse_slurm_mem [ Functions ]

[ Top ] [ m_argparse ] [ Functions ]

NAME

  parse_slurm_mem

FUNCTION

  Parse `arg` string with memory given in Slurm syntax. Return value in Mb.
  From https://slurm.schedmd.com/sbatch.html

  --mem=<size>[units]

  Default units are megabytes. Different units can be specified using the suffix [K|M|G|T].

  For a list of slurm env variables that can be used to pass options to Abinit via the submission script, see:
  https://docs.hpc.shef.ac.uk/en/latest/referenceinfo/scheduler/SLURM/SLURM-environment-variables.html

SOURCE

417 real(dp) function parse_slurm_mem(arg, optname) result(mem_mb)
418 
419 !Arguments ------------------------------------
420  character(len=*),intent(in) :: arg,optname
421 
422 !Local variables-------------------------------
423  integer :: istop, istat
424  real(dp) :: fact
425  character(len=500) :: iomsg
426 ! *************************************************************************
427 
428  fact = one
429  istop = find_and_select(arg, &
430                          ["K", "M", "G", "T"], &
431                          [one/1024._dp, one, 1024._dp, 1024._dp ** 2], fact, iomsg, default=one)
432 
433  ABI_CHECK(istop /= -1, iomsg)
434  istop = merge(len_trim(arg), istop - 1, istop == 0)
435 
436  read(arg(len(optname) + 1: istop), *, iostat=istat, iomsg=iomsg) mem_mb
437  ABI_CHECK(istat == 0, sjoin("Invalid syntax for memory string:", arg, ch10, "iomsg", iomsg))
438  ABI_CHECK(mem_mb > zero, "mem_mb must be positive!")
439  mem_mb = mem_mb * fact
440 
441 end function parse_slurm_mem

m_argparse/parse_yesno [ Functions ]

[ Top ] [ m_argparse ] [ Functions ]

NAME

  parse_yesno

FUNCTION

  This function receives an argument, arg of the form --foo[=bool_value]
  that begins with optname (i.e. --foo) and returns the value of bool_value
  If bool_value is not present, returns default (.True. if not specified)

SOURCE

373 logical function parse_yesno(arg, optname, default) result(bool)
374 
375 !Arguments ------------------------------------
376  character(len=*),intent(in) :: arg,optname
377  logical,optional,intent(in) :: default
378 ! *************************************************************************
379 
380  bool = .True.; if (present(default)) bool = default
381 
382  ! Assume default if value is not given
383  if (len_trim(optname) == len_trim(arg)) return
384 
385  select case (arg(len(optname)+1:))
386  case ("=yes", "=y")
387    bool = .True.
388  case ("=no", "=n")
389    bool = .False.
390  case default
391    write(std_out,*)"Wrong option ",trim(arg),". Will default to ",bool
392    ABI_ERROR("Aborting now")
393  end select
394 
395 end function parse_yesno