|
V3FIT
|
Go to the documentation of this file.
43 CHARACTER (len=6) :: signal_id
74 CHARACTER (len=*),
INTENT(in) :: file
75 CHARACTER (len=*),
INTENT(in) :: signal_id
79 REAL (rprec) :: start_time
82 INTEGER,
PARAMETER :: iou_0 = 32
93 &
'Error opening ',
' file.')
114 REAL (rprec) :: start_time
120 CLOSE(signal_dot_file_ref%iou)
153 CHARACTER (len=*),
INTENT(in) :: coordinate_type
154 CHARACTER (len=data_short_name_length),
INTENT(out) :: chord_name
155 REAL(rprec),
DIMENSION(3),
INTENT(out) :: xcart_i
156 REAL(rprec),
DIMENSION(3),
OPTIONAL,
INTENT(out) :: xcart_f
160 CHARACTER (len=signal_dot_line_len) :: line
161 REAL (rprec) :: start_time
168 &
'Error reading ID for ',
' chord.')
169 chord_name = trim(line)
173 &
'Error reading start ' //
174 &
'position for chord.')
176 IF (
PRESENT(xcart_f))
THEN
179 &
'Error reading end ' //
180 &
'position for chord.')
184 IF (trim(coordinate_type) .eq.
'RPHiDegZ')
THEN
185 xcart_i(2) = xcart_i(2)*degree
188 IF (
PRESENT(xcart_f))
THEN
189 xcart_f(2) = xcart_f(2)*degree
216 CHARACTER (len=*),
INTENT(in) :: message
220 CHARACTER (len=signal_dot_line_len) :: line
221 REAL (rprec) :: start_time
257 CHARACTER (len=*),
INTENT(in) :: message
261 CHARACTER (len=signal_dot_line_len) :: line
262 REAL (rprec) :: start_time
298 CHARACTER (len=*),
INTENT(in) :: message
302 CHARACTER (len=signal_dot_line_len) :: line
303 REAL (rprec) :: start_time
338 CHARACTER (len=*),
INTENT(in) :: message
342 CHARACTER (len=signal_dot_line_len) :: line
343 REAL (rprec) :: start_time
350 &
'Error ', message))
378 CHARACTER (len=*),
INTENT(in) :: message
382 CHARACTER (len=signal_dot_line_len) :: line
383 REAL (rprec) :: start_time
418 CHARACTER (len=*),
DIMENSION(:),
INTENT(in) :: keywords
422 CHARACTER (len=signal_dot_line_len) :: line
423 REAL (rprec) :: start_time
433 &
' keyword before end of file.')
434 DO i = 1,
SIZE(keywords)
435 IF (trim(adjustl(line)) .eq. trim(keywords(i)))
THEN
472 CHARACTER (len=*),
INTENT(in) :: pre_message
473 CHARACTER (len=*),
INTENT(in) :: post_message
477 REAL (rprec) :: start_time
482 READ (signal_dot_file_ref%iou,
'(a)', iostat=status)
484 signal_dot_file_ref%i_line = signal_dot_file_ref%i_line + 1
486 & pre_message, post_message)
509 & signal_dot_file_ref, &
515 INTEGER,
INTENT(in) :: status
517 CHARACTER (len=*),
INTENT(in) :: pre_message
518 CHARACTER (len=*),
INTENT(in) :: post_message
521 REAL (rprec) :: start_time
526 IF (status .ne. 0)
THEN
527 WRITE(*,*) pre_message // trim(signal_dot_file_ref%signal_id)
528 & // post_message //
' line ',
529 & signal_dot_file_ref%i_line
Defines functions for measuring an tabulating performance of function and subroutine calls....
Module is part of the LIBSTELL. This modules containes code to convert from different coordinate syst...
integer function signal_dot_parse_int(signal_dot_file_ref, message)
Parse a single integer from a diagnostic dot file.
Base class representing a diagnostic dot file. This is an opaqe class.
real(rprec) function, dimension(3) signal_dot_parse_3_real(signal_dot_file_ref, message)
Parse a three reals from a diagnostic dot file.
Defines the base class of type signal_dot_file. This module contains common code used in parsing diag...
real(rprec) function profiler_get_start_time()
Gets the start time of profiled function.
subroutine, private signal_dot_check_status(status, signal_dot_file_ref, pre_message, post_message)
Check and handle errors.
real(rprec) function, public signal_dot_parse_real(signal_dot_file_ref, message)
Parse a single real from a diagnostic dot file.
pure real(rprec) function, dimension(3), public cyl_to_cart(cyl)
Convert a point from cylindical coordinates to cartesian coordinates.
integer function, dimension(2) signal_dot_parse_2_int(signal_dot_file_ref, message)
Parse two integers from a diagnostic dot file.
integer, parameter signal_dot_line_len
Maximum line length.
This modules contains parameters used by equilibrium models.
subroutine, public signal_dot_parse_chord(signal_dot_file_ref, coordinate_type, chord_name, xcart_i, xcart_f)
Parse a chord from a diagnostic dot file.
type(signal_dot_file) function, public signal_dot_open(file, signal_id)
Open a diagnostic dot file.
subroutine profiler_set_stop_time(symbol_name, start_time)
Gets the end time of profiled function.
character(len=signal_dot_line_len) function, public signal_dot_read_line(signal_dot_file_ref, pre_message, post_message)
Read line from diagnostic dot file.
character(len=data_name_length) function, public signal_dot_read_keyword(signal_dot_file_ref, keywords)
Read a keyword from the diagnostic dot file.
subroutine, public signal_dot_close(signal_dot_file_ref)
Close a diagnostic dot file.
real(rprec) function, dimension(2) signal_dot_parse_2_real(signal_dot_file_ref, message)
Parse a two reals from a diagnostic dot file.