|
V3FIT
|
Go to the documentation of this file.
98 CHARACTER (len=max_length) :: command
100 CHARACTER (len=max_arg_length),
DIMENSION(:),
POINTER ::
104 CHARACTER (len=path_length),
DIMENSION(:),
POINTER ::
132 CHARACTER (len=max_length) :: temp
133 INTEGER :: num_args, i, value_index
134 REAL (rprec) :: start_time
148 IF (num_args .le. 0)
THEN
159 CALL getcarg(i, temp, num_args)
162 IF (temp(1:1) .eq.
'-')
THEN
163 value_index = index(temp,
'=')
164 IF (value_index .eq. 0)
THEN
166 IF (trim(temp) .eq.
'-h')
THEN
174 & temp(1:value_index - 1)
176 & temp(value_index + 1:len_trim(temp))
206 TYPE (commandline_parser_class),
POINTER :: this
209 IF (
ASSOCIATED(this%arg))
THEN
214 IF (
ASSOCIATED(this%value))
THEN
215 DEALLOCATE(this%value)
244 CHARACTER (len=*),
INTENT(in) :: arg
248 REAL (rprec) :: start_time
256 IF (
ASSOCIATED(this%arg))
THEN
257 DO i = 1,
SIZE(this%arg)
258 IF (trim(this%arg(i)) .eq. trim(arg))
THEN
262 &
'commandline_parser_get_string', start_time)
295 CHARACTER (len=*),
INTENT(in) :: arg
296 INTEGER,
INTENT(in) :: default_value
299 CHARACTER (len=path_length) :: value
301 REAL (rprec) :: start_time
308 IF (trim(
value) .eq.
'')
THEN
319 IF (status .ne. 0)
THEN
350 CHARACTER (len=*),
INTENT(in) :: arg
351 REAL (rprec),
INTENT(in) :: default_value
354 CHARACTER (len=path_length) :: value
356 REAL (rprec) :: start_time
363 IF (trim(
value) .eq.
'')
THEN
374 IF (status .ne. 0)
THEN
403 CHARACTER (len=*),
INTENT(in) :: arg
407 REAL (rprec) :: start_time
415 IF (
ASSOCIATED(this%arg))
THEN
416 DO i = 1,
SIZE(this%arg)
417 IF (trim(this%arg(i)) .eq. trim(arg))
THEN
421 &
'commandline_parser_is_flag_set', start_time)
455 WRITE(*,*)
'Configured with: '
458 WRITE(*,*)
' MPI support '
461 WRITE(*,*)
'Usage: xv3fit [-arg][=option] ... '
463 WRITE(*,*)
'Options: '
464 WRITE(*,*)
'All options are displayed as [arg][takesoption][text]'
465 WRITE(*,*)
' -h N Display this information '
467 WRITE(*,*)
' -d N Use default namelist input file '
469 WRITE(*,*)
' -file Y Specify the v3fit namelist input file '
471 WRITE(*,*)
' -test N Run unit tests '
473 WRITE(*,*)
' -force N Forces the equilibrium to resolve on '
474 WRITE(*,*)
' every reconstruction parameter. '
480 WRITE(*,*)
' -out N Write out the input file and at each '
483 WRITE(*,*)
' -c Y Compress magnetic response functions '
484 WRITE(*,*)
' using the cutoff. Overwrites the value '
485 WRITE(*,*)
' in the namelist input. '
487 WRITE(*,*)
' -c_diff N Use central differencing to compute the '
488 WRITE(*,*)
' Jacobian. '
490 WRITE(*,*)
' -serial N Run the reconstruction serially and with'
491 WRITE(*,*)
' parallel equilibria. '
493 WRITE(*,*)
' -restart Y Specify v3fit to restart from the '
494 WRITE(*,*)
' provided result file. Must have the last'
495 WRITE(*,*)
' valid wout and/or siesta restart file. '
498 WRITE(*,*)
' If no -arg is found -file is implicitly implied. '
499 WRITE(*,*)
'The default input filename is v3fit.in. '
Defines functions for measuring an tabulating performance of function and subroutine calls....
real(rprec) function commandline_parser_get_real(this, arg, default_value)
Get the value of an argument as a Real.
Base class containing a parsed commandline.
integer, parameter, private max_arg_length
Maximum length of the argument including the '-' character.
Defines the base class of the type commandline_parser_class.
type(commandline_parser_class) function, pointer commandline_parser_construct()
Construct a commandline_parser_class object.
integer function commandline_parser_get_integer(this, arg, default_value)
Get the value of an argument as an integer.
logical function commandline_parser_is_flag_set(this, arg)
Check if a command line argument was set.
subroutine commandline_parser_destruct(this)
Deconstruct a commandline_parser_class object.
character(len=path_length) function commandline_parser_get_string(this, arg)
Get the value of an argument as a string.
real(rprec) function profiler_get_start_time()
Gets the start time of profiled function.
Contains cross platform routines for manipulating files on the file system. Defines a functions to mo...
integer, parameter commandline_parser_no_error
Commandline argument not found.
subroutine commandline_parser_print_help
Print out help text.
integer, parameter, private max_length
Maximum length of the complete flag. All command line flags take the form of '-flag=value'.
subroutine profiler_set_stop_time(symbol_name, start_time)
Gets the end time of profiled function.
integer, parameter path_length
Length of file paths.
integer, parameter commandline_parser_arg_not_found
Commandline argument not found.