V3FIT
thscte_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 !
62 !-------------------------------------------------------------------------------
63 !*******************************************************************************
66 !
67 ! Note separating the Doxygen comment block here so detailed decription is
68 ! found in the Module not the file.
69 !
72 !*******************************************************************************
73  MODULE thscte_dot
74 
75  USE stel_kinds
76  USE stel_constants
77  USE signal_dot
78 
79  IMPLICIT NONE
80 
81  CONTAINS
82 !*******************************************************************************
83 ! UTILITY SUBROUTINES
84 !*******************************************************************************
85 !-------------------------------------------------------------------------------
100 !-------------------------------------------------------------------------------
101  SUBROUTINE thscte_dot_read(thscte_file, signals, signals_created, &
102  & observed, sigma, weight, first_index)
103  USE signal
104  USE data_parameters
105 
106  IMPLICIT NONE
107 
108 ! Declare Arguments
109  CHARACTER (len=path_length), INTENT(in) :: thscte_file
110  TYPE (signal_pointer), DIMENSION(:), INTENT(inout) :: signals
111  INTEGER, INTENT(inout) :: signals_created
112  REAL (rprec), DIMENSION(:), INTENT(in) :: observed
113  REAL (rprec), DIMENSION(:), INTENT(in) :: sigma
114  REAL (rprec), DIMENSION(:), INTENT(in) :: weight
115  INTEGER, INTENT(inout) :: first_index
116 
117 ! local parameters
118 ! n_thscted_keyword integer - number of thscted_keyword s.
119  INTEGER, PARAMETER :: n_thscted_keyword = 9
120 
121 ! local variables
122 ! thscted_keyword character array - keywords for various thscte input types
123  CHARACTER(len=data_name_length), &
124  & DIMENSION(1:n_thscted_keyword) :: thscted_keyword
125  TYPE(signal_dot_file) :: thscte_dot_file_ref
126  REAL (rprec) :: start_time
127 
128 ! Start of executable code
129  start_time = profiler_get_start_time()
130 
131 ! Initialize the keywords and keyword lengths
132  thscted_keyword(1) = 'thscte_XYZ'
133  thscted_keyword(2) = 'thscte_RPhiDegZ'
134  thscted_keyword(3) = 'thscte_XYZ_te'
135  thscted_keyword(4) = 'thscte_RPhiDegZ_te'
136  thscted_keyword(5) = 'thscte_XYZ_ne'
137  thscted_keyword(6) = 'thscte_RPhiDegZ_ne'
138  thscted_keyword(7) = 'thscte_XYZ_pres'
139  thscted_keyword(8) = 'thscte_RPhiDegZ_pres'
140  thscted_keyword(9) = 'end_of_file'
141 
142 ! Open up the 'thscte.' file
143  thscte_dot_file_ref = signal_dot_open(trim(thscte_file), &
144  & 'thscte')
145 
146 ! Infinite Loop
147 ! Character variable line should be defined on entry
148  DO
149 ! Branch on the keyword
150  SELECT CASE (signal_dot_read_keyword(thscte_dot_file_ref, &
151  & thscted_keyword))
152 
153  CASE DEFAULT ! This case should never fire.
154  EXIT ! Exit out of infinte loop.
155 
156  CASE ('end_of_file')
157  EXIT ! Exit out of infinte loop.
158 
159  CASE ('thscte_XYZ','thscte_XYZ_te')
160  CALL thscte_dot_parse_chord(thscte_dot_file_ref, &
161  & 'XYZ', 't', &
162  & signals, signals_created, &
163  & observed, sigma, weight, &
164  & first_index)
165 
166  CASE ('thscte_RPhiDegZ','thscte_RPhiDegZ_te')
167  CALL thscte_dot_parse_chord(thscte_dot_file_ref, &
168  & 'RPHiDegZ', 't', &
169  & signals, signals_created, &
170  & observed, sigma, weight, &
171  & first_index)
172 
173  CASE ('thscte_XYZ_ne')
174  CALL thscte_dot_parse_chord(thscte_dot_file_ref, &
175  & 'XYZ', 'd', &
176  & signals, signals_created, &
177  & observed, sigma, weight, &
178  & first_index)
179 
180  CASE ('thscte_RPhiDegZ_ne')
181  CALL thscte_dot_parse_chord(thscte_dot_file_ref, &
182  & 'RPHiDegZ', 'd', &
183  & signals, signals_created, &
184  & observed, sigma, weight, &
185  & first_index)
186 
187  CASE ('thscte_XYZ_pres')
188  CALL thscte_dot_parse_chord(thscte_dot_file_ref, &
189  & 'XYZ', 'p', &
190  & signals, signals_created, &
191  & observed, sigma, weight, &
192  & first_index)
193 
194  CASE ('thscte_RPhiDegZ_pres')
195  CALL thscte_dot_parse_chord(thscte_dot_file_ref, &
196  & 'RPHiDegZ', 'p', &
197  & signals, signals_created, &
198  & observed, sigma, weight, &
199  & first_index)
200 
201  END SELECT
202 
203  END DO
204 
205 ! Close the 'thscte.' file
206  CALL signal_dot_close(thscte_dot_file_ref)
207 
208  CALL profiler_set_stop_time('thscte_dot_read', start_time)
209 
210  END SUBROUTINE
211 
212 !*******************************************************************************
213 ! PARSING SUBROUTINES
214 !*******************************************************************************
215 !-------------------------------------------------------------------------------
238 !-------------------------------------------------------------------------------
239  SUBROUTINE thscte_dot_parse_chord(thscte_dot_file_ref, &
240  & coordinate_type, &
241  & point_type, &
242  & signals, &
243  & signals_created, &
244  & observed, sigma, weight, &
245  & first_index)
247  USE v3fit_input, only: v3fit_max_diagnostics, &
250  USE v3_utilities, only: err_fatal
251  IMPLICIT NONE
252 
253 ! Declare Arguments
254  TYPE(signal_dot_file), INTENT(inout) :: thscte_dot_file_ref
255  CHARACTER (len=*) :: coordinate_type
256  CHARACTER (len=1) :: point_type
257  TYPE (signal_pointer), DIMENSION(:), INTENT(inout) :: signals
258  INTEGER, INTENT(inout) :: signals_created
259  REAL (rprec), DIMENSION(:), INTENT(in) :: observed
260  REAL (rprec), DIMENSION(:), INTENT(in) :: sigma
261  REAL (rprec), DIMENSION(:), INTENT(in) :: weight
262  INTEGER, INTENT(inout) :: first_index
263 
264 ! local variables
265  REAL (rprec), DIMENSION(3) :: xcart
266  CHARACTER (len=data_short_name_length) :: point_name
267  class(thomson_class), POINTER :: thomson_obj => null()
268  CHARACTER (len=data_short_name_length) :: units = ''
269  REAL (rprec) :: start_time
270 
271 ! Start of executable code
272  start_time = profiler_get_start_time()
273 
274 ! Check if there are two many signals.
275  IF (signals_created + 1 .gt. v3fit_max_diagnostics) THEN
276  CALL err_fatal('thscte_dot_parse_chord: created signals' // &
277  & ' exceeds v3fit_max_diagnostics')
278  END IF
279 
280 ! Get the position and name of the point.
281  CALL signal_dot_parse_chord(thscte_dot_file_ref, &
282  & coordinate_type, &
283  & point_name, &
284  & xcart)
285 
286  SELECT CASE (point_type)
287 
288  CASE ('t')
289  thomson_obj => thomson_te_class(xcart)
290  units = 'ev'
291 
292  CASE ('d')
293  thomson_obj => thomson_ne_class(xcart)
294  units = 'm^-3'
295 
296  CASE ('p')
297  thomson_obj => thomson_p_class(xcart)
298  units = 'Pa'
299 
300  END SELECT
301 
302  CALL signal_construct( thomson_obj, point_name, point_name, &
303  & units, observed(signals_created + 1), &
304  & sigma(signals_created + 1), weight(signals_created + 1), &
305  & v3fit_input_find_scale_index(signals_created + 1), &
306  & v3fit_input_find_offset_index(signals_created + 1))
307 
308  signals(signals_created + 1)%p => thomson_obj
309 
310  signals_created = signals_created + 1
311 
312 ! At lease one thomson scattering signal was made. Set the first index. This
313 ! should only be run once.
314  IF (first_index .eq. -1) THEN
315  first_index = signals_created
316  END IF
317 
318  CALL profiler_set_stop_time('thscte_dot_parse_chord', start_time)
319 
320  END SUBROUTINE
321 
322  END MODULE
thscte_dot::thscte_dot_read
subroutine thscte_dot_read(thscte_file, signals, signals_created, observed, sigma, weight, first_index)
Read an thomson scattering diagnostic dot file.
Definition: thscte_dot.f:103
v3fit_input::v3fit_max_diagnostics
integer, parameter v3fit_max_diagnostics
Maximum number of diagnostic signals.
Definition: v3fit_input.f:582
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
signal_dot::signal_dot_file
Base class representing a diagnostic dot file. This is an opaqe class.
Definition: signal_dot.f:36
thomson::thomson_te_class
Base class representing a thomson scattering te signal.
Definition: thomson.f:58
thomson::thomson_p_class
Base class representing a thomson scattering te signal.
Definition: thomson.f:84
thomson::thomson_class
Base class representing a thomson scattering signal.
Definition: thomson.f:45
thscte_dot::thscte_dot_parse_chord
subroutine thscte_dot_parse_chord(thscte_dot_file_ref, coordinate_type, point_type, signals, signals_created, observed, sigma, weight, first_index)
Parse thomson scattering diagnostic chord.
Definition: thscte_dot.f:246
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
thscte_dot
Module for opening and reading a 'thscte.' file. The file format for these files are documented in Th...
Definition: thscte_dot.f:73
thomson
Implements thomson scattering diagnostic. Defines the base class of the type thomson_class.
Definition: thomson.f:14
data_parameters
This modules contains parameters used by equilibrium models.
Definition: data_parameters.f:10
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
thomson::thomson_ne_class
Base class representing a thomson scattering te signal.
Definition: thomson.f:71
signal_dot::signal_dot_close
subroutine, public signal_dot_close(signal_dot_file_ref)
Close a diagnostic dot file.
Definition: signal_dot.f:107