V3FIT
ece_dot.f
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
2 ! The @fixed_width, @begin_table, @item2 and @end_table commands are custom
3 ! defined commands in Doxygen.in. They are defined under ALIASES. For the page
4 ! created here, the 80 column limit is exceeded. Arguments of aliases are
5 ! separated by ','. If you intended ',' to be a string you must use an escaped
6 ! comma '\,'.
7 !
63 !-------------------------------------------------------------------------------
64 !*******************************************************************************
67 !
68 ! Note separating the Doxygen comment block here so detailed decription is
69 ! found in the Module not the file.
70 !
73 !*******************************************************************************
74 
75  MODULE ece_dot
76 
77  USE stel_kinds
78  USE stel_constants
79  USE signal_dot
80 
81  IMPLICIT NONE
82 
83  CONTAINS
84 !*******************************************************************************
85 ! UTILITY SUBROUTINES
86 !*******************************************************************************
87 !-------------------------------------------------------------------------------
103 !-------------------------------------------------------------------------------
104  SUBROUTINE ece_dot_read(ece_file, signals, signals_created, &
105  & observed, sigma, weight, first_index)
106  USE signal
107  USE data_parameters
108 
109  IMPLICIT NONE
110 
111 ! Declare Arguments
112  CHARACTER (len=path_length), INTENT(in) :: ece_file
113  TYPE (signal_pointer), DIMENSION(:), INTENT(inout) :: signals
114  INTEGER, INTENT(inout) :: signals_created
115  REAL (rprec), DIMENSION(:), INTENT(in) :: observed
116  REAL (rprec), DIMENSION(:), INTENT(in) :: sigma
117  REAL (rprec), DIMENSION(:), INTENT(in) :: weight
118  INTEGER, INTENT(inout) :: first_index
119 
120 ! local parameters
121 ! n_ece_keyword integer - number of ece_keyword s.
122  INTEGER, PARAMETER :: n_ece_keyword = 3
123 
124 ! local variables
125 ! ece_keyword character array - keywords for various ece input types
126  CHARACTER(len=data_name_length), DIMENSION(1:n_ece_keyword) :: &
127  & ece_keyword
128  TYPE(signal_dot_file) :: ece_dot_file_ref
129  INTEGER :: current_profile
130  REAL (rprec) :: start_time
131 
132 ! Start of executable code
133  start_time = profiler_get_start_time()
134 
135 ! Initialize the keywords
136  ece_keyword(1) = 'ece_chord_XYZ'
137  ece_keyword(2) = 'ece_chord_RPhiDegZ'
138  ece_keyword(3) = 'end_of_file'
139 
140 ! Open up the 'ece.' file
141  ece_dot_file_ref = signal_dot_open(trim(ece_file), 'ece')
142 
143 ! Infinite Loop
144 ! Character variable line should be defined on entry
145  DO
146 ! Branch on the keyword
147  SELECT CASE (signal_dot_read_keyword(ece_dot_file_ref, &
148  & ece_keyword))
149 
150  CASE DEFAULT ! This case should never fire.
151  EXIT ! Exit out of infinte loop.
152 
153  CASE ('end_of_file')
154  EXIT ! Exit out of infinte loop.
155 
156  CASE ('ece_chord_XYZ')
157  CALL ece_dot_parse_chord(ece_dot_file_ref, 'XYZ', &
158  & signals, signals_created, &
159  & observed, sigma, weight, &
160  & first_index)
161 
162  CASE ('ece_chord_RPhiDegZ')
163  CALL ece_dot_parse_chord(ece_dot_file_ref, 'RPHiDegZ', &
164  & signals, signals_created, &
165  & observed, sigma, weight, &
166  & first_index)
167 
168  END SELECT
169 
170  END DO
171 
172 ! Close the 'ece.' file
173  CALL signal_dot_close(ece_dot_file_ref)
174 
175  CALL profiler_set_stop_time('ece_dot_read', start_time)
176 
177  END SUBROUTINE
178 
179 !*******************************************************************************
180 ! PARSING SUBROUTINES
181 !*******************************************************************************
182 !-------------------------------------------------------------------------------
203 !-------------------------------------------------------------------------------
204  SUBROUTINE ece_dot_parse_chord(ece_dot_file_ref, coordinate_type, &
205  & signals, signals_created, observed, &
206  & sigma, weight, first_index)
207  USE ece
208  USE v3fit_input, only: v3fit_max_diagnostics, &
211  USE v3_utilities, only: err_fatal
212 
213  IMPLICIT NONE
214 
215 ! Declare Arguments
216  TYPE (signal_dot_file), INTENT(inout) :: ece_dot_file_ref
217  CHARACTER (len=*), INTENT(in) :: coordinate_type
218  TYPE (signal_pointer), DIMENSION(:), INTENT(inout) :: signals
219  INTEGER, INTENT(inout) :: signals_created
220  REAL (rprec), DIMENSION(:), INTENT(in) :: observed
221  REAL (rprec), DIMENSION(:), INTENT(in) :: sigma
222  REAL (rprec), DIMENSION(:), INTENT(in) :: weight
223  INTEGER, INTENT(inout) :: first_index
224 
225 ! local variables
226  class(ece_class), POINTER :: ece_obj
227  REAL(rprec), DIMENSION(3) :: xcart_i
228  REAL(rprec), DIMENSION(3) :: xcart_f
229  CHARACTER (len=data_short_name_length) :: chord_name
230  REAL (rprec) :: resonance
231  REAL (rprec) :: start_time
232 
233 ! Start of executable code
234  start_time = profiler_get_start_time()
235 
236 ! Check if there are two many signals.
237  IF (signals_created + 1 .gt. v3fit_max_diagnostics) THEN
238  CALL err_fatal('ece_dot_parse_chord_new: created signals' // &
239  & ' exceeds v3fit_max_diagnostics')
240  END IF
241 
242 ! Get the start, end and name of chord.
243  CALL signal_dot_parse_chord(ece_dot_file_ref, coordinate_type, &
244  & chord_name, xcart_i, xcart_f)
245 
246 ! Default the geometric factor to 1.
247  resonance = signal_dot_parse_real(ece_dot_file_ref, &
248  & 'Expected resonance for ECE chord')
249 
250  ece_obj => ece_class(xcart_i, xcart_f, resonance)
251  CALL signal_construct_new(ece_obj, chord_name, chord_name, 'arb', &
252  & observed(signals_created + 1), &
253  & sigma(signals_created + 1), weight(signals_created + 1), &
254  & v3fit_input_find_scale_index(signals_created + 1), &
255  & v3fit_input_find_offset_index(signals_created + 1))
256 
257  signals(signals_created + 1)%p => ece_obj
258  signals_created = signals_created + 1
259 
260 ! At lease one ece signal was made. Set the first index. This should only be
261 ! run once.
262  IF (first_index .eq. -1) THEN
263  first_index = signals_created
264  END IF
265 
266  CALL profiler_set_stop_time('ece_dot_parse_chord', start_time)
267 
268  END SUBROUTINE
269 
270  END MODULE
v3fit_input::v3fit_max_diagnostics
integer, parameter v3fit_max_diagnostics
Maximum number of diagnostic signals.
Definition: v3fit_input.f:582
ece::ece_class
Base class representing an ECE signal.
Definition: ece.f:32
v3fit_input::v3fit_input_find_scale_index
integer function v3fit_input_find_scale_index(index)
Finds the index of the scaling spec.
Definition: v3fit_input.f:1521
v3fit_input
This file contains all the variables and maximum sizes of the inputs for a v3fit namelist input file....
Definition: v3fit_input.f:570
ece_dot::ece_dot_parse_chord
subroutine ece_dot_parse_chord(ece_dot_file_ref, coordinate_type, signals, signals_created, observed, sigma, weight, first_index)
Parse ECE diagnostic chord.
Definition: ece_dot.f:207
signal_dot
Defines the base class of type signal_dot_file. This module contains common code used in parsing diag...
Definition: signal_dot.f:14
signal_dot::signal_dot_parse_real
real(rprec) function, public signal_dot_parse_real(signal_dot_file_ref, message)
Parse a single real from a diagnostic dot file.
Definition: signal_dot.f:211
ece_dot::ece_dot_read
subroutine ece_dot_read(ece_file, signals, signals_created, observed, sigma, weight, first_index)
Read an ECE diagnostic dot file.
Definition: ece_dot.f:106
data_parameters
This modules contains parameters used by equilibrium models.
Definition: data_parameters.f:10
ece
Defines the base class of the type ece_class.
Definition: ece.f:13
signal_dot::signal_dot_parse_chord
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.
Definition: signal_dot.f:147
signal_dot::signal_dot_open
type(signal_dot_file) function, public signal_dot_open(file, signal_id)
Open a diagnostic dot file.
Definition: signal_dot.f:68
signal_dot::signal_dot_read_keyword
character(len=data_name_length) function, public signal_dot_read_keyword(signal_dot_file_ref, keywords)
Read a keyword from the diagnostic dot file.
Definition: signal_dot.f:412
v3fit_input::v3fit_input_find_offset_index
integer function v3fit_input_find_offset_index(index)
Finds the index of the offset spec.
Definition: v3fit_input.f:1563
signal
Defines the base class of the type signal_class.
Definition: signal.f:14
signal_dot::signal_dot_close
subroutine, public signal_dot_close(signal_dot_file_ref)
Close a diagnostic dot file.
Definition: signal_dot.f:107
ece_dot
Module for opening and reading a 'ece.' file. The file format for these files are documented in ECE D...
Definition: ece_dot.f:75