! 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 type cli_options ! Switches logical :: quiet ! Files character(len=:), allocatable :: output_dir character(len=:), allocatable :: params_file character(len=:), allocatable :: sum_filelist ! others integer :: verbose integer, allocatable :: units(:) end type private public :: cli_options, print_cli_options, parse_cli_options 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 parameters file' print '(a)', ' (default: gray_params.data)' print '(a)', ' -s, --sum FILE sum the output profiles from a list of files' print '(a)', ' -u, --units ID[,ID...] select which units to output (default: 4, 7)' 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)', ' 2 if serious trouble (e.g., computation failed).' 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) implicit none ! 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)' , ' - units: ' , opts%units print '(a,l)' , ' - verbose: ' , opts%verbose end subroutine subroutine parse_cli_options(opts) ! Parse the CLI arguments and initialise the options use units, only : ucenr, usumm use logger, only : WARNING implicit none ! subroutine arguments type(cli_options), intent(out) :: opts ! local variables character(len=:), allocatable :: argument, temp logical :: skip_next = .false. integer :: i, nargs integer :: error, commas ! Default option values opts%verbose = WARNING opts%quiet = .false. opts%params_file = 'gray_params.data' opts%units = [ucenr, usumm] nargs = command_argument_count() do i = 1, nargs call get_command_string(i, argument) ! skip one cycle if the last argument was a value if (skip_next) then skip_next = .false. cycle end if ! parse an argument (and possibly a value) select case (argument) case ('-h', '--help') call print_help() call exit(0) case ('-V', '--version') call print_version() call exit(0) case ('-v', '--verbose') opts%verbose = opts%verbose + 1 case ('-q', '--quiet') opts%quiet = .true. case ('-o', '--output-dir') call get_command_string(i + 1, opts%output_dir) skip_next = .true. case ('-p', '--params-file') call get_command_string(i + 1, opts%params_file) skip_next = .true. case ('-s', '--sum') call get_command_string(i + 1, opts%sum_filelist) skip_next = .true. case ('-u', '--units') call get_command_string(i + 1, temp) ! resize the array commas = count([(temp(i:i) == ',', i = 1, len(temp))]) deallocate(opts%units) allocate(opts%units(commas + 1)) ! read the list of table IDs read(temp, *, iostat=error) opts%units if (error .gt. 0) then print '(a,a)', 'invalid table IDs: ', temp call exit(1) end if deallocate(temp) skip_next = .true. case default print '(a,a,/)', 'Unknown option: ', argument call print_help() call exit(1) end select end do ! free temporary string if (nargs .gt. 0) deallocate(argument) end subroutine subroutine get_command_string(i, arg) ! Reads a CLI argument into a deferred-length string implicit none ! subroutine arguments integer, intent(in) :: 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 end subroutine end module gray_cli