V3FIT
commandline_parser.f
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
2 ! The @header2, @begin_table, @item3 and @end_table commands are custom defined
3 ! commands in Doxygen.in. They are defined under ALIASES. For the page created
4 ! here, the 80 column limit is exceeded. Arguments of aliases are separated by
5 ! ','. If you intended ',' to be a string you must use an escaped comma '\,'.
6 !
54 !-------------------------------------------------------------------------------
55 !*******************************************************************************
58 !
59 ! Note separating the Doxygen comment block here so detailed decription is
60 ! found in the Module not the file.
61 !
63 !*******************************************************************************
64 
66  USE stel_kinds
67  USE file_opts, only: path_length
68  USE profiler
69 
70  IMPLICIT NONE
71 
72 !*******************************************************************************
73 ! commandline parser module parameters
74 !*******************************************************************************
76  INTEGER, PARAMETER, PRIVATE :: max_arg_length = 8
79  INTEGER, PARAMETER, PRIVATE :: max_length = path_length &
80  & + max_arg_length + 1
81 
82 ! Commandline parser error codes.
84  INTEGER, PARAMETER :: commandline_parser_no_error = 0
86  INTEGER, PARAMETER :: commandline_parser_arg_not_found = -1
87 
88 !*******************************************************************************
89 ! DERIVED-TYPE DECLARATIONS
90 ! 1) commandline parser base class
91 !
92 !*******************************************************************************
93 !-------------------------------------------------------------------------------
95 !-------------------------------------------------------------------------------
98  CHARACTER (len=max_length) :: command
100  CHARACTER (len=max_arg_length), DIMENSION(:), POINTER :: &
101  & arg => null()
104  CHARACTER (len=path_length), DIMENSION(:), POINTER :: &
105  & value => null()
106  END TYPE
107 
108  CONTAINS
109 !*******************************************************************************
110 ! CONSTRUCTION SUBROUTINES
111 !*******************************************************************************
112 !-------------------------------------------------------------------------------
122 !-------------------------------------------------------------------------------
124 
125  IMPLICIT NONE
126 
127 ! Declare Arguments
128  TYPE (commandline_parser_class), POINTER :: &
130 
131 ! local variables
132  CHARACTER (len=max_length) :: temp
133  INTEGER :: num_args, i, value_index
134  REAL (rprec) :: start_time
135 
136 ! Start of executable code
137  start_time = profiler_get_start_time()
138 
139  temp = ''
140  num_args = 0
141  value_index = 0
143 
144 ! Read the zeroith arg to get the number of arguments. This should also be the
145 ! command name.
146  CALL getcarg(0, commandline_parser_construct%command, num_args)
147 
148  IF (num_args .le. 0) THEN
150  END IF
151 
152 ! Allocate the arrays and
153  ALLOCATE(commandline_parser_construct%arg(num_args))
154  ALLOCATE(commandline_parser_construct%value(num_args))
155 
156 ! Loop through the command line arguments, and setup the argument and value
157 ! arrays
158  DO i = 1, num_args
159  CALL getcarg(i, temp, num_args)
160 
161 ! Check for a - as the first character.
162  IF (temp(1:1) .eq. '-') THEN
163  value_index = index(temp, '=')
164  IF (value_index .eq. 0) THEN
165 ! Check for help command.
166  IF (trim(temp) .eq. '-h') THEN
168  END IF
169 
170  commandline_parser_construct%arg(i) = trim(temp)
171  commandline_parser_construct%value(i) = ''
172  ELSE
174  & temp(1:value_index - 1)
175  commandline_parser_construct%value(i) = &
176  & temp(value_index + 1:len_trim(temp))
177  END IF
178  ELSE
179 ! Implicity set the argument to -file
180  commandline_parser_construct%arg(i) = '-file'
181  commandline_parser_construct%value(i) = &
182  & temp(1:path_length)
183  END IF
184  END DO
185 
186  CALL profiler_set_stop_time('commandline_parser_construct', &
187  & start_time)
188 
189  END FUNCTION
190 
191 !*******************************************************************************
192 ! DESTRUCTION SUBROUTINES
193 !*******************************************************************************
194 !-------------------------------------------------------------------------------
200 !-------------------------------------------------------------------------------
201  SUBROUTINE commandline_parser_destruct(this)
202 
203  IMPLICIT NONE
204 
205 ! Declare Arguments
206  TYPE (commandline_parser_class), POINTER :: this
207 
208 ! Start of executable code
209  IF (ASSOCIATED(this%arg)) THEN
210  DEALLOCATE(this%arg)
211  this%arg => null()
212  END IF
213 
214  IF (ASSOCIATED(this%value)) THEN
215  DEALLOCATE(this%value)
216  this%value => null()
217  END IF
218 
219  DEALLOCATE(this)
220 
221  END SUBROUTINE
222 
223 !*******************************************************************************
224 ! GETTER SUBROUTINES
225 !*******************************************************************************
226 !-------------------------------------------------------------------------------
236 !-------------------------------------------------------------------------------
237  FUNCTION commandline_parser_get_string(this, arg)
238 
239  IMPLICIT NONE
240 
241 ! Declare Arguments
242  CHARACTER (len=path_length) :: commandline_parser_get_string
243  TYPE (commandline_parser_class), INTENT(in) :: this
244  CHARACTER (len=*), INTENT(in) :: arg
245 
246 ! Local arguments
247  INTEGER :: i
248  REAL (rprec) :: start_time
249 
250 ! Start of executable code
251  start_time = profiler_get_start_time()
252 
253 ! Loop through the arguments until the correct arg is found.
255 
256  IF (ASSOCIATED(this%arg)) THEN
257  DO i = 1, SIZE(this%arg)
258  IF (trim(this%arg(i)) .eq. trim(arg)) THEN
259  commandline_parser_get_string = this%value(i)
260 
261  CALL profiler_set_stop_time( &
262  & 'commandline_parser_get_string', start_time)
263 
264  RETURN
265  END IF
266  END DO
267  END IF
268 
269  CALL profiler_set_stop_time('commandline_parser_get_string', &
270  & start_time)
271 
272  END FUNCTION
273 
274 !-------------------------------------------------------------------------------
286 !-------------------------------------------------------------------------------
287  FUNCTION commandline_parser_get_integer(this, arg, &
288  & default_value)
289 
290  IMPLICIT NONE
291 
292 ! Declare Arguments
294  TYPE (commandline_parser_class), INTENT(in) :: this
295  CHARACTER (len=*), INTENT(in) :: arg
296  INTEGER, INTENT(in) :: default_value
297 
298 ! Local arguments
299  CHARACTER (len=path_length) :: value
300  INTEGER :: status
301  REAL (rprec) :: start_time
302 
303 ! Start of executable code
304  start_time = profiler_get_start_time()
305 
306  value = commandline_parser_get_string(this, arg)
307 
308  IF (trim(value) .eq. '') THEN
309  commandline_parser_get_integer = default_value
310 
311  CALL profiler_set_stop_time('commandline_parser_get_integer', &
312  & start_time)
313 
314  RETURN
315  END IF
316 
317  READ (value,1000,iostat=status) commandline_parser_get_integer
318 
319  IF (status .ne. 0) THEN
320  commandline_parser_get_integer = default_value
321  END IF
322 
323  CALL profiler_set_stop_time('commandline_parser_get_integer', &
324  & start_time)
325 
326 1000 FORMAT(i20)
327 
328  END FUNCTION
329 
330 !-------------------------------------------------------------------------------
342 !-------------------------------------------------------------------------------
343  FUNCTION commandline_parser_get_real(this, arg, default_value)
344 
345  IMPLICIT NONE
346 
347 ! Declare Arguments
348  REAL (rprec) :: commandline_parser_get_real
349  TYPE (commandline_parser_class), INTENT(in) :: this
350  CHARACTER (len=*), INTENT(in) :: arg
351  REAL (rprec), INTENT(in) :: default_value
352 
353 ! Local arguments
354  CHARACTER (len=path_length) :: value
355  INTEGER :: status
356  REAL (rprec) :: start_time
357 
358 ! Start of executable code
359  start_time = profiler_get_start_time()
360 
361  value = commandline_parser_get_string(this, arg)
362 
363  IF (trim(value) .eq. '') THEN
364  commandline_parser_get_real = default_value
365 
366  CALL profiler_set_stop_time('commandline_parser_get_real', &
367  & start_time)
368 
369  RETURN
370  END IF
371 
372  READ (value,*,iostat=status) commandline_parser_get_real
373 
374  IF (status .ne. 0) THEN
375  commandline_parser_get_real = default_value
376  END IF
377 
378  CALL profiler_set_stop_time('commandline_parser_get_real', &
379  & start_time)
380 
381  END FUNCTION
382 
383 !*******************************************************************************
384 ! QUERY SUBROUTINES
385 !*******************************************************************************
386 !-------------------------------------------------------------------------------
395 !-------------------------------------------------------------------------------
396  FUNCTION commandline_parser_is_flag_set(this, arg)
397 
398  IMPLICIT NONE
399 
400 ! Declare Arguments
402  TYPE (commandline_parser_class), INTENT(in) :: this
403  CHARACTER (len=*), INTENT(in) :: arg
404 
405 ! Local arguments
406  INTEGER :: i
407  REAL (rprec) :: start_time
408 
409 ! Start of executable code
410  start_time = profiler_get_start_time()
411 
412 ! Loop through the arguments until the correct arg is found.
414 
415  IF (ASSOCIATED(this%arg)) THEN
416  DO i = 1, SIZE(this%arg)
417  IF (trim(this%arg(i)) .eq. trim(arg)) THEN
419 
420  CALL profiler_set_stop_time( &
421  & 'commandline_parser_is_flag_set', start_time)
422 
423  RETURN
424  END IF
425  END DO
426  END IF
427 
428  CALL profiler_set_stop_time('commandline_parser_is_flag_set', &
429  & start_time)
430 
431  END FUNCTION
432 
433 !*******************************************************************************
434 ! UTILITY SUBROUTINES
435 !*******************************************************************************
436 !-------------------------------------------------------------------------------
444 !-------------------------------------------------------------------------------
446 
447  IMPLICIT NONE
448 
449 ! Start of executable code
450 ! All command line messages need to fit within this width.
451 ! ' s c '
452  WRITE(*,*) ' '
453  WRITE(*,*) ' V3FIT '
454  WRITE(*,*) ' '
455  WRITE(*,*) 'Configured with: '
456 !$ WRITE(*,*) ' OpenMP support '
457 #if defined(MPI_OPT)
458  WRITE(*,*) ' MPI support '
459 #endif
460  WRITE(*,*) ' '
461  WRITE(*,*) 'Usage: xv3fit [-arg][=option] ... '
462  WRITE(*,*) ' '
463  WRITE(*,*) 'Options: '
464  WRITE(*,*) 'All options are displayed as [arg][takesoption][text]'
465  WRITE(*,*) ' -h N Display this information '
466  WRITE(*,*) ' '
467  WRITE(*,*) ' -d N Use default namelist input file '
468  WRITE(*,*) ' '
469  WRITE(*,*) ' -file Y Specify the v3fit namelist input file '
470  WRITE(*,*) ' '
471  WRITE(*,*) ' -test N Run unit tests '
472  WRITE(*,*) ' '
473  WRITE(*,*) ' -force N Forces the equilibrium to resolve on '
474  WRITE(*,*) ' every reconstruction parameter. '
475  WRITE(*,*) ' '
476 !$ WRITE(*,*) ' -para Y Determines number of parallel insatnces '
477 !$ WRITE(*,*) ' to run with. A value of -1 means use the'
478 !$ WRITE(*,*) ' default number of threads. '
479 !$ WRITE(*,*) ' '
480  WRITE(*,*) ' -out N Write out the input file and at each '
481  WRITE(*,*) ' step. '
482  WRITE(*,*) ' '
483  WRITE(*,*) ' -c Y Compress magnetic response functions '
484  WRITE(*,*) ' using the cutoff. Overwrites the value '
485  WRITE(*,*) ' in the namelist input. '
486  WRITE(*,*) ' '
487  WRITE(*,*) ' -c_diff N Use central differencing to compute the '
488  WRITE(*,*) ' Jacobian. '
489  WRITE(*,*) ' '
490  WRITE(*,*) ' -serial N Run the reconstruction serially and with'
491  WRITE(*,*) ' parallel equilibria. '
492  WRITE(*,*) ' '
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. '
496  WRITE(*,*) ' '
497  WRITE(*,*) 'Notes: '
498  WRITE(*,*) ' If no -arg is found -file is implicitly implied. '
499  WRITE(*,*) 'The default input filename is v3fit.in. '
500  WRITE(*,*) ' '
501 
502  stop
503 
504  END SUBROUTINE
505 
506  END MODULE
profiler
Defines functions for measuring an tabulating performance of function and subroutine calls....
Definition: profiler.f:13
commandline_parser::commandline_parser_get_real
real(rprec) function commandline_parser_get_real(this, arg, default_value)
Get the value of an argument as a Real.
Definition: commandline_parser.f:344
commandline_parser::commandline_parser_class
Base class containing a parsed commandline.
Definition: commandline_parser.f:96
commandline_parser::max_arg_length
integer, parameter, private max_arg_length
Maximum length of the argument including the '-' character.
Definition: commandline_parser.f:76
commandline_parser
Defines the base class of the type commandline_parser_class.
Definition: commandline_parser.f:65
commandline_parser::commandline_parser_construct
type(commandline_parser_class) function, pointer commandline_parser_construct()
Construct a commandline_parser_class object.
Definition: commandline_parser.f:124
commandline_parser::commandline_parser_get_integer
integer function commandline_parser_get_integer(this, arg, default_value)
Get the value of an argument as an integer.
Definition: commandline_parser.f:289
commandline_parser::commandline_parser_is_flag_set
logical function commandline_parser_is_flag_set(this, arg)
Check if a command line argument was set.
Definition: commandline_parser.f:397
commandline_parser::commandline_parser_destruct
subroutine commandline_parser_destruct(this)
Deconstruct a commandline_parser_class object.
Definition: commandline_parser.f:202
commandline_parser::commandline_parser_get_string
character(len=path_length) function commandline_parser_get_string(this, arg)
Get the value of an argument as a string.
Definition: commandline_parser.f:238
profiler::profiler_get_start_time
real(rprec) function profiler_get_start_time()
Gets the start time of profiled function.
Definition: profiler.f:194
file_opts
Contains cross platform routines for manipulating files on the file system. Defines a functions to mo...
Definition: file_opts.f:13
commandline_parser::commandline_parser_no_error
integer, parameter commandline_parser_no_error
Commandline argument not found.
Definition: commandline_parser.f:84
commandline_parser::commandline_parser_print_help
subroutine commandline_parser_print_help
Print out help text.
Definition: commandline_parser.f:446
commandline_parser::max_length
integer, parameter, private max_length
Maximum length of the complete flag. All command line flags take the form of '-flag=value'.
Definition: commandline_parser.f:79
profiler::profiler_set_stop_time
subroutine profiler_set_stop_time(symbol_name, start_time)
Gets the end time of profiled function.
Definition: profiler.f:121
file_opts::path_length
integer, parameter path_length
Length of file paths.
Definition: file_opts.f:22
commandline_parser::commandline_parser_arg_not_found
integer, parameter commandline_parser_arg_not_found
Commandline argument not found.
Definition: commandline_parser.f:86