V3FIT
sxrch_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 !
96 !-------------------------------------------------------------------------------
97 !*******************************************************************************
100 !
101 ! Note separating the Doxygen comment block here so detailed decription is
102 ! found in the Module not the file.
103 !
106 !*******************************************************************************
107 
108  MODULE sxrch_dot
109 
110  USE stel_kinds
111  USE stel_constants
112  USE signal_dot
113 
114  IMPLICIT NONE
115 
116  CONTAINS
117 !*******************************************************************************
118 ! UTILITY SUBROUTINES
119 !*******************************************************************************
120 !-------------------------------------------------------------------------------
136 !-------------------------------------------------------------------------------
137  SUBROUTINE sxrch_dot_read(sxrch_file, signals, signals_created, &
138  & observed, sigma, weight, first_index)
139  USE signal
140  USE data_parameters
141 
142  IMPLICIT NONE
143 
144 ! Declare Arguments
145  CHARACTER (len=path_length), INTENT(in) :: sxrch_file
146  TYPE (signal_pointer), DIMENSION(:), INTENT(inout) :: signals
147  INTEGER, INTENT(inout) :: signals_created
148  REAL (rprec), DIMENSION(:), INTENT(in) :: observed
149  REAL (rprec), DIMENSION(:), INTENT(in) :: sigma
150  REAL (rprec), DIMENSION(:), INTENT(in) :: weight
151  INTEGER, INTENT(inout) :: first_index
152 
153 ! local parameters
154 ! n_sxrchd_keyword integer - number of sxrchd_keyword s.
155  INTEGER, PARAMETER :: n_sxrchd_keyword = 10
156 
157 ! local variables
158 ! sxrchd_keyword character array - keywords for various sxrch input types
159  CHARACTER(len=data_name_length), DIMENSION(1:n_sxrchd_keyword) :: &
160  & sxrchd_keyword
161  TYPE(signal_dot_file) :: sxrch_dot_file_ref
162  INTEGER :: current_profile
163  REAL (rprec) :: start_time
164 
165 ! Start of executable code
166  start_time = profiler_get_start_time()
167 
168 ! Initialize the keywords
169  sxrchd_keyword(1) = 'sxr_chord_XYZ'
170  sxrchd_keyword(2) = 'sxr_chord_RPhiDegZ'
171  sxrchd_keyword(3) = 'sxr_chord_XYZ_geo'
172  sxrchd_keyword(4) = 'sxr_chord_RPhiDegZ_geo'
173  sxrchd_keyword(5) = 'sxr_chord_XYZ_xics_emiss'
174  sxrchd_keyword(6) = 'sxr_chord_RPhiDegZ_xics_emiss'
175  sxrchd_keyword(7) = 'sxr_chord_XYZ_xics_ti'
176  sxrchd_keyword(8) = 'sxr_chord_RPhiDegZ_xics_ti'
177  sxrchd_keyword(9) = 'sxr_new_profile'
178  sxrchd_keyword(10) = 'end_of_file'
179 
180 ! Open up the 'sxrch.' file
181  sxrch_dot_file_ref = signal_dot_open(trim(sxrch_file), 'sxrch')
182 
183 ! Start with the first profile
184  current_profile = 1
185 
186 ! Infinite Loop
187 ! Character variable line should be defined on entry
188  DO
189 ! Branch on the keyword
190  SELECT CASE (signal_dot_read_keyword(sxrch_dot_file_ref, &
191  & sxrchd_keyword))
192 
193  CASE DEFAULT ! This case should never fire.
194  EXIT ! Exit out of infinte loop.
195 
196  CASE ('end_of_file')
197  EXIT ! Exit out of infinte loop.
198 
199  CASE ('sxr_chord_XYZ', 'sxr_chord_XYZ_xics_emiss')
200  CALL sxrch_dot_parse_chord(sxrch_dot_file_ref, &
201  & 'XYZ', signals, &
202  & signals_created, &
203  & observed, sigma, weight, &
204  & current_profile, first_index, &
205  & .false., .false.)
206 
207  CASE ('sxr_chord_RPhiDegZ', 'sxr_chord_RPhiDegZ_xics_emiss')
208  CALL sxrch_dot_parse_chord(sxrch_dot_file_ref, &
209  & 'RPHiDegZ', signals, &
210  & signals_created, &
211  & observed, sigma, weight, &
212  & current_profile, first_index, &
213  & .false., .false.)
214 
215  CASE ('sxr_chord_XYZ_geo')
216  CALL sxrch_dot_parse_chord(sxrch_dot_file_ref, &
217  & 'XYZ', signals, &
218  & signals_created, &
219  & observed, sigma, weight, &
220  & current_profile, first_index, &
221  & .true., .false.)
222 
223  CASE ('sxr_chord_RPhiDegZ_geo')
224  CALL sxrch_dot_parse_chord(sxrch_dot_file_ref, &
225  & 'RPHiDegZ', signals, &
226  & signals_created, &
227  & observed, sigma, weight, &
228  & current_profile, first_index, &
229  & .true., .false.)
230 
231  CASE ('sxr_chord_XYZ_xics_ti')
232  CALL sxrch_dot_parse_chord(sxrch_dot_file_ref, &
233  & 'XYZ', signals, &
234  & signals_created, &
235  & observed, sigma, weight, &
236  & current_profile, first_index, &
237  & .false., .true.)
238 
239  CASE ('sxr_chord_RPhiDegZ_xics_ti')
240  CALL sxrch_dot_parse_chord(sxrch_dot_file_ref, &
241  & 'RPHiDegZ', signals, &
242  & signals_created, &
243  & observed, sigma, weight, &
244  & current_profile, first_index, &
245  & .false., .true.)
246 
247  CASE ('sxr_new_profile')
248  current_profile = current_profile + 1
249 
250  END SELECT
251 
252  END DO
253 
254 ! Close the 'sxrch.' file
255  CALL signal_dot_close(sxrch_dot_file_ref)
256 
257  CALL profiler_set_stop_time('sxrch_dot_read', start_time)
258 
259  END SUBROUTINE
260 
261 !*******************************************************************************
262 ! PARSING SUBROUTINES
263 !*******************************************************************************
264 !-------------------------------------------------------------------------------
287 !-------------------------------------------------------------------------------
288  SUBROUTINE sxrch_dot_parse_chord(sxrch_dot_file_ref, &
289  & coordinate_type, &
290  & signals, &
291  & signals_created, &
292  & observed, sigma, weight, &
293  & current_profile, first_index, &
294  & use_geo, is_ti)
295  USE sxrem
296  USE v3fit_input, only: v3fit_max_diagnostics, &
299  USE v3_utilities, only: err_fatal
300 
301  IMPLICIT NONE
302 
303 ! Declare Arguments
304  TYPE (signal_dot_file), INTENT(inout) :: sxrch_dot_file_ref
305  CHARACTER (len=*), INTENT(in) :: coordinate_type
306  TYPE (signal_pointer), DIMENSION(:), INTENT(inout) :: signals
307  INTEGER, INTENT(inout) :: signals_created
308  REAL (rprec), DIMENSION(:), INTENT(in) :: observed
309  REAL (rprec), DIMENSION(:), INTENT(in) :: sigma
310  REAL (rprec), DIMENSION(:), INTENT(in) :: weight
311  INTEGER, INTENT(in) :: current_profile
312  INTEGER, INTENT(inout) :: first_index
313  LOGICAL, INTENT(in) :: use_geo
314  LOGICAL, INTENT(in) :: is_ti
315 
316 ! local variables
317  REAL(rprec), DIMENSION(3) :: xcart_i, xcart_f
318  CHARACTER (len=data_short_name_length) :: chord_name
319  REAL (rprec) :: geo
320  class(sxrem_class), POINTER :: sxrem_obj
321  REAL (rprec) :: start_time
322 
323 ! Start of executable code
324  start_time = profiler_get_start_time()
325 
326 ! Check if there are two many signals.
327  IF (signals_created + 1 .gt. v3fit_max_diagnostics) THEN
328  CALL err_fatal('sxrch_dot_parse_chord_new: created signals' // &
329  & ' exceeds v3fit_max_diagnostics')
330  END IF
331 
332 ! Get the start, end and name of chord.
333  CALL signal_dot_parse_chord(sxrch_dot_file_ref, &
334  & coordinate_type, &
335  & chord_name, &
336  & xcart_i, xcart_f)
337 
338 ! Default the geometric factor to 1.
339  geo = 1.0
340  IF (use_geo) THEN
341  geo = signal_dot_parse_real(sxrch_dot_file_ref, &
342  & 'Expected geometric factor for sxrem chord')
343  END IF
344 
345  IF (is_ti) THEN
346  sxrem_obj => sxrem_ti_class(xcart_i, xcart_f, current_profile)
347  CALL signal_construct(sxrem_obj, chord_name, chord_name, 'eVm', &
348  & observed(signals_created + 1), &
349  & sigma(signals_created + 1), &
350  & weight(signals_created + 1), &
351  & v3fit_input_find_scale_index(signals_created + 1), &
352  & v3fit_input_find_offset_index(signals_created + 1))
353  ELSE
354  sxrem_obj => sxrem_emiss_class(xcart_i, xcart_f, geo, &
355  & current_profile)
356  CALL signal_construct(sxrem_obj, chord_name, chord_name, 'arb', &
357  & observed(signals_created + 1), &
358  & sigma(signals_created + 1), &
359  & weight(signals_created + 1), &
360  & v3fit_input_find_scale_index(signals_created + 1), &
361  & v3fit_input_find_offset_index(signals_created + 1))
362  END IF
363 
364  signals(signals_created + 1)%p => sxrem_obj
365 
366  signals_created = signals_created + 1
367 
368 ! At lease one sxrem signal was made. Set the first index. This should only be
369 ! run once.
370  IF (first_index .eq. -1) THEN
371  first_index = signals_created
372  END IF
373 
374  CALL profiler_set_stop_time('sxrch_dot_parse_chord', start_time)
375 
376  END SUBROUTINE
377 
378  END MODULE
sxrch_dot
Module for opening and reading a 'sxrch.' file. The file format for these files are documented in Sof...
Definition: sxrch_dot.f:108
sxrch_dot::sxrch_dot_parse_chord
subroutine sxrch_dot_parse_chord(sxrch_dot_file_ref, coordinate_type, signals, signals_created, observed, sigma, weight, current_profile, first_index, use_geo, is_ti)
Parse soft x-ray diagnostic chord.
Definition: sxrch_dot.f:295
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
sxrem::sxrem_ti_class
Base class representing a soft x-ray ti signal.
Definition: sxrem.f:67
sxrch_dot::sxrch_dot_read
subroutine sxrch_dot_read(sxrch_file, signals, signals_created, observed, sigma, weight, first_index)
Read a soft x-ray diagnostic dot file.
Definition: sxrch_dot.f:139
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
sxrem
Defines the base class of the type sxrem_class.
Definition: sxrem.f:13
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
sxrem::sxrem_class
Base class representing a soft x-ray signal.
Definition: sxrem.f:35
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
sxrem::sxrem_emiss_class
Base class representing a soft x-ray emissivity signal.
Definition: sxrem.f:49
signal_dot::signal_dot_close
subroutine, public signal_dot_close(signal_dot_file_ref)
Close a diagnostic dot file.
Definition: signal_dot.f:107