! This module implements the command-line interface (CLI) of GRAY module gray_cli implicit none ! GRAY command line options ! See print_help() for a description. ! Note: if you change these, remember to update: ! 1. the print_help() subroutine ! 2. the print_cli_options() subroutine ! 3. the man page type cli_options ! Switches logical :: quiet ! Files character(len=:), allocatable :: output_dir character(len=:), allocatable :: params_file character(len=:), allocatable :: config_file character(len=:), allocatable :: sum_filelist ! others integer :: verbose integer, allocatable :: tables(:) end type private public :: cli_options, print_cli_options, parse_cli_options, & parse_param_overrides, print_version, get_next_command contains subroutine print_help() ! Prints the usage screen print '(a)', 'Usage: gray [OPTIONS]' print '(a)', '' print '(a)', 'GRAY is a beam-tracing code for Electron Cyclotron (EC) waves in a tokamak.' print '(a)', 'It is based on the complex eikonal theory (quasi-optics), which can accurately' print '(a)', 'describe the propagation of a Gaussian beam, diffraction effects included.' print '(a)', 'In addition, power absoption and current drive are computed using the fully' print '(a)', 'relativistic dispersion relation and a neoclassical response function,' print '(a)', 'respectively.' print '(a)', '' print '(a)', 'Options:' print '(a)', ' -h, --help display this help and exit' print '(a)', ' -V, --version display version information and exit' print '(a)', ' -v, --verbose print more information messages;' print '(a)', ' repeating -v increase the log verbosity' print '(a)', ' -q, --quiet suppress all non-critical messages' print '(a)', ' -o, --output-dir DIR specify where to write the output files' print '(a)', ' (default: current directory)' print '(a)', ' -p, --params-file FILE set the (legacy) parameters file' print '(a)', ' (default: gray_params.data)' print '(a)', ' -c, --config-file FILE set the (new) GRAY config file' print '(a)', ' (default: gray.ini)' print '(a)', ' -s, --sum FILE sum the output profiles from a list of files' print '(a)', ' -t, --tables ID[,ID...] select which tables to write (default: 4, 7);' print '(a)', ' use `all` to enable all, or `none` for no tables.' print '(a)', ' see the manual for all unit IDs.' print '(a)', ' -g, --gray-param ID=VAL set a GRAY parameter, overriding the value' print '(a)', ' specified via --params-file/--config-file;' print '(a)', ' the ID is GROUP.NAME, ex. antenna.fghz;' print '(a)', ' see the manual for available parameters.' print '(a)', '' print '(a)', '*Exit status*' print '(a)', ' 0 if OK,' print '(a)', ' 1 if technical problems (e.g., invalid arguments, missing input files),' print '(a)', ' >1 if simulation trouble (e.g., unstable gradient, negative absorption).' print '(a)', '' print '(a)', 'Full documentation is available at' print '(a)', '' end subroutine subroutine print_version() ! Prints the version information print '(a)', 'gray revision ' // REVISION print '(a)', '' print '(a)', 'Written by D. Farina, L. Figini, A. Mariani and M. Guerini Rocco.' end subroutine subroutine print_cli_options(opts) ! Prints the parsed CLI options (for debugging) ! subroutine arguments type(cli_options), intent(in) :: opts print '(a)' , 'switches:' print '(a,l)' , ' - quiet: ' , opts%quiet print '(a)' , 'files:' print '(a,a)' , ' output-dir: ' , opts%output_dir print '(a,a)' , ' param-file: ' , opts%params_file print '(a,a)' , ' sum: ' , opts%sum_filelist print '(a)' , 'others:' print '(a,20i3)' , ' - tables: ' , opts%tables print '(a,l)' , ' - verbose: ' , opts%verbose end subroutine subroutine parse_cli_options(opts) ! Parse the CLI arguments and initialise the options use logger, only : WARNING ! subroutine arguments type(cli_options), intent(out) :: opts ! local variables character(len=:), allocatable :: argument, temp integer :: i, nargs integer :: error, commas ! Default option values opts%verbose = WARNING opts%quiet = .false. opts%params_file = 'gray_params.data' opts%tables = [4, 7] nargs = command_argument_count() i = 1 do if (i > nargs) exit call get_next_command(i, argument) ! parse an argument (and possibly a value) select case (argument) case ('-h', '--help') call print_help() deallocate(argument) call exit(0) case ('-V', '--version') call print_version() deallocate(argument) call exit(0) case ('-v', '--verbose') opts%verbose = opts%verbose + 1 case ('-q', '--quiet') opts%quiet = .true. case ('-o', '--output-dir') call get_next_command(i, opts%output_dir) case ('-p', '--params-file') call get_next_command(i, opts%params_file) case ('-c', '--config-file') call get_next_command(i, opts%config_file) case ('-s', '--sum') call get_next_command(i, opts%sum_filelist) case ('-t', '--tables') call get_next_command(i, temp) if (temp == 'none') then ! disable all output tables deallocate(opts%tables) allocate(opts%tables(0)) elseif (temp == 'all') then ! enable all output tables deallocate(opts%tables) opts%tables = [-1] else ! resize the array commas = count([(temp(i:i) == ',', i = 1, len(temp))]) deallocate(opts%tables) allocate(opts%tables(commas + 1)) ! read the list of table IDs read (temp, *, iostat=error) opts%tables if (error > 0) then print '(a,a)', 'invalid table IDs: ', temp deallocate(argument) deallocate(temp) call exit(1) end if end if deallocate(temp) case ('-g', '--gray-param') ! these overrides are parsed later since they need to ! be applied to the final gray_parameters structure i = i + 1 case default print '(a,a,/)', 'Unknown option: ', argument call print_help() deallocate(argument) call exit(1) end select end do ! free temporary string if (nargs > 0) deallocate(argument) end subroutine subroutine parse_param_overrides(params) ! Reads GRAY parameters from CLI and overrides `params` accordingly use gray_params, only : gray_parameters, update_parameter use ini_parser, only : ERR_VALUE, ERR_UNKNOWN ! subroutine arguments type(gray_parameters), intent(inout) :: params ! local variables character(len=:), allocatable :: argument, temp, id, val integer :: i, nargs integer :: sep nargs = command_argument_count() i = 1 do if (i > nargs) exit call get_next_command(i, argument) ! parse gray parameters select case (argument) case ('-g', '--gray-param') call get_next_command(i, temp) ! split at "=" (id=value) sep = index(temp, '=') id = temp(1:sep - 1) val = temp(sep + 1:) if (sep == 0) then print '(a,a)', 'invalid GRAY parameter declaration: ', temp print '(a)', 'correct syntax is ID=VALUE, ex. antenna.alpha=45' deallocate(temp) call exit(1) end if ! match the name string to a parameter select case (update_parameter(params, id, val)) case (ERR_VALUE) print '(4a)', 'invalid value for ', id, ': ', val deallocate(temp) call exit(1) case (ERR_UNKNOWN) print '(a,a)', 'unknown GRAY parameter: ', id deallocate(temp) call exit(1) end select deallocate(temp) ! skip everything else case default cycle end select end do ! free temporary string if (nargs > 0) deallocate(argument) end subroutine parse_param_overrides subroutine get_next_command(i, arg) ! Reads a CLI argument into a deferred-length string ! subroutine arguments integer, intent(inout) :: i character(len=:), allocatable, intent(inout) :: arg ! local variables integer :: len if (allocated(arg)) deallocate(arg) ! free memory (if needed) call get_command_argument(i, length=len) ! get the arg length allocate(character(len) :: arg) ! allocate memory call get_command_argument(i, arg) ! copy i = i + 1 ! increment counter end subroutine end module gray_cli