V3FIT
mse_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 !
117 !-------------------------------------------------------------------------------
118 !*******************************************************************************
121 !
122 ! Note separating the Doxygen comment block here so detailed decription is
123 ! found in the Module not the file.
124 !
127 !*******************************************************************************
128 
129  MODULE mse_dot
130 
131  USE stel_kinds
132  USE stel_constants
133  USE signal_dot
134 
135  IMPLICIT NONE
136 
137  CONTAINS
138 !*******************************************************************************
139 ! UTILITY SUBROUTINES
140 !*******************************************************************************
141 !-------------------------------------------------------------------------------
156 !-------------------------------------------------------------------------------
157  SUBROUTINE mse_dot_read(mse_file, signals, signals_created, &
158  & observed, sigma, weight, first_index)
159  USE signal
160  USE data_parameters
161 
162  IMPLICIT NONE
163 
164 ! Declare Arguments
165  CHARACTER (len=path_length), INTENT(in) :: mse_file
166  TYPE (signal_pointer), DIMENSION(:), INTENT(inout) :: signals
167  INTEGER, INTENT(inout) :: signals_created
168  REAL (rprec), DIMENSION(:), INTENT(in) :: observed
169  REAL (rprec), DIMENSION(:), INTENT(in) :: sigma
170  REAL (rprec), DIMENSION(:), INTENT(in) :: weight
171  INTEGER, INTENT(inout) :: first_index
172 
173 ! local parameters
174 ! n_mse_keyword integer - number of mse_keyword s.
175  INTEGER, PARAMETER :: n_mse_keyword = 19
176 
177 ! local variables
178 ! mse_keyword character array - keywords for various ipch input types
179  CHARACTER(len=data_name_length), DIMENSION(1:n_mse_keyword) :: &
180  & mse_keyword
181  TYPE (signal_dot_file) :: mse_dot_file_ref
182  REAL (rprec) :: start_time
183 
184 ! Start of executable code
185  start_time = profiler_get_start_time()
186 
187 ! Initialize the keywords and keyword lengths
188  mse_keyword(1) = 'mse_point_XYZ_deg'
189  mse_keyword(2) = 'mse_point_RPhiDegZ_deg'
190  mse_keyword(3) = 'mse_point_XYZ_rad'
191  mse_keyword(4) = 'mse_point_RPhiDegZ_rad'
192  mse_keyword(5) = 'mse_point_XYZ_deg_deg'
193  mse_keyword(6) = 'mse_point_RPhiDegZ_deg_deg'
194  mse_keyword(7) = 'mse_point_XYZ_rad_deg'
195  mse_keyword(8) = 'mse_point_RPhiDegZ_rad_deg'
196  mse_keyword(9) = 'mse_point_XYZ_deg_rad'
197  mse_keyword(10) = 'mse_point_RPhiDegZ_deg_rad'
198  mse_keyword(11) = 'mse_point_XYZ_rad_rad'
199  mse_keyword(12) = 'mse_point_RPhiDegZ_rad_rad'
200  mse_keyword(13) = 'mse_point_XYZ_ratio'
201  mse_keyword(14) = 'mse_point_RPhiDegZ_ratio'
202  mse_keyword(15) = 'mse_point_XYZ_deg_ratio'
203  mse_keyword(16) = 'mse_point_RPhiDegZ_deg_ratio'
204  mse_keyword(17) = 'mse_point_XYZ_rad_ratio'
205  mse_keyword(18) = 'mse_point_RPhiDegZ_rad_ratio'
206  mse_keyword(19) = 'end_of_file'
207 
208 ! Open up the 'mse.' file
209  mse_dot_file_ref = signal_dot_open(trim(mse_file), 'mse')
210 
211 ! Infinite Loop
212 ! Character variable line should be defined on entry
213  DO
214 ! Branch on the keyword
215  SELECT CASE (signal_dot_read_keyword(mse_dot_file_ref, &
216  & mse_keyword))
217 
218  CASE DEFAULT ! This case should never fire.
219  EXIT ! Exit out of infinte loop.
220 
221  CASE ('end_of_file')
222  EXIT ! Exit out of infinte loop.
223 
224  CASE ('mse_point_XYZ_deg')
225  CALL mse_dot_parse_vec(mse_dot_file_ref, 'XYZ', signals, &
226  & signals_created, observed, sigma, &
227  & weight, first_index, .true., &
228  & .false.)
229 
230  CASE ('mse_point_RPhiDegZ_deg')
231  CALL mse_dot_parse_vec(mse_dot_file_ref, 'RPhiDegZ', &
232  & signals, signals_created, &
233  & observed, sigma, weight, &
234  & first_index, .true., .false.)
235 
236  CASE ('mse_point_XYZ_rad')
237  CALL mse_dot_parse_vec(mse_dot_file_ref, 'XYZ', signals, &
238  & signals_created, observed, sigma, &
239  & weight, first_index, .false., &
240  & .false.)
241 
242  CASE ('mse_point_RPhiDegZ_rad')
243  CALL mse_dot_parse_vec(mse_dot_file_ref, 'RPhiDegZ', &
244  & signals, signals_created, &
245  & observed, sigma, weight, &
246  & first_index, .false., .false.)
247 
248  CASE ('mse_point_XYZ_deg_deg')
249  CALL mse_dot_parse_ang(mse_dot_file_ref, 'XYZ', signals, &
250  & signals_created, observed, sigma, &
251  & weight, first_index, .true., &
252  & .true., .false.)
253 
254  CASE ('mse_point_RPhiDegZ_deg_deg')
255  CALL mse_dot_parse_ang(mse_dot_file_ref, 'RPhiDegZ', &
256  & signals, signals_created, &
257  & observed, sigma, weight, &
258  & first_index, .true., .true., &
259  & .false.)
260 
261  CASE ('mse_point_XYZ_rad_deg')
262  CALL mse_dot_parse_ang(mse_dot_file_ref, 'XYZ', signals, &
263  & signals_created, observed, sigma, &
264  & weight, first_index, .false., &
265  & .true., .false.)
266 
267  CASE ('mse_point_RPhiDegZ_rad_deg')
268  CALL mse_dot_parse_ang(mse_dot_file_ref, 'RPhiDegZ', &
269  & signals, signals_created, &
270  & observed, sigma, weight, &
271  & first_index, .false., .true., &
272  & .false.)
273 
274  CASE ('mse_point_XYZ_deg_rad')
275  CALL mse_dot_parse_ang(mse_dot_file_ref, 'XYZ', signals, &
276  & signals_created, observed, sigma, &
277  & weight, first_index, .true., &
278  & .false., .false.)
279 
280  CASE ('mse_point_RPhiDegZ_deg_rad')
281  CALL mse_dot_parse_ang(mse_dot_file_ref, 'RPhiDegZ', &
282  & signals, signals_created, &
283  & observed, sigma, weight, &
284  & first_index, .true., .false., &
285  & .false.)
286 
287  CASE ('mse_point_XYZ_rad_rad')
288  CALL mse_dot_parse_ang(mse_dot_file_ref, 'XYZ', signals, &
289  & signals_created, observed, sigma, &
290  & weight, first_index, .false., &
291  & .false., .false.)
292 
293  CASE ('mse_point_RPhiDegZ_rad_rad')
294  CALL mse_dot_parse_ang(mse_dot_file_ref, 'RPhiDegZ', &
295  & signals, signals_created, &
296  & observed, sigma, weight, &
297  & first_index, .false., .false., &
298  & .false.)
299 
300  CASE ('mse_point_XYZ_ratio')
301  CALL mse_dot_parse_vec(mse_dot_file_ref, 'XYZ', signals, &
302  & signals_created, observed, sigma, &
303  & weight, first_index, .true., &
304  & .true.)
305 
306  CASE ('mse_point_RPhiDegZ_ratio')
307  CALL mse_dot_parse_vec(mse_dot_file_ref, 'RPhiDegZ', &
308  & signals, signals_created, &
309  & observed, sigma, weight, &
310  & first_index, .true., .true.)
311 
312  CASE ('mse_point_XYZ_deg_ratio')
313  CALL mse_dot_parse_ang(mse_dot_file_ref, 'XYZ', signals, &
314  & signals_created, observed, sigma, &
315  & weight, first_index, .true., &
316  & .true., .true.)
317 
318  CASE ('mse_point_RPhiDegZ_deg_ratio')
319  CALL mse_dot_parse_ang(mse_dot_file_ref, 'RPhiDegZ', &
320  & signals, signals_created, &
321  & observed, sigma, weight, &
322  & first_index, .true., .true., &
323  & .true.)
324 
325  CASE ('mse_point_XYZ_rad_ratio')
326  CALL mse_dot_parse_ang(mse_dot_file_ref, 'XYZ', signals, &
327  & signals_created, observed, sigma, &
328  & weight, first_index, .false., &
329  & .true., .true.)
330 
331  CASE ('mse_point_RPhiDegZ_rad_ratio')
332  CALL mse_dot_parse_ang(mse_dot_file_ref, 'RPhiDegZ', &
333  & signals, signals_created, &
334  & observed, sigma, weight, &
335  & first_index, .false., .true., &
336  & .true.)
337 
338  END SELECT
339 
340  END DO
341 
342 ! Close the 'mse.' file
343  CALL signal_dot_close(mse_dot_file_ref)
344 
345  CALL profiler_set_stop_time('mse_dot_read', start_time)
346 
347  END SUBROUTINE
348 
349 !*******************************************************************************
350 ! PARSING SUBROUTINES
351 !*******************************************************************************
352 !-------------------------------------------------------------------------------
377 !-------------------------------------------------------------------------------
378  SUBROUTINE mse_dot_parse_vec(mse_dot_file_ref, coordinate_type, &
379  & signals, signals_created, &
380  & observed, sigma, weight, &
381  & first_index, in_degrees, is_ratio)
382  USE mse
383  USE v3fit_input, only: v3fit_max_diagnostics, &
386  USE v3_utilities, only: err_fatal
388 
389  IMPLICIT NONE
390 
391 ! Declare Arguments
392  TYPE (signal_dot_file), INTENT(inout) :: mse_dot_file_ref
393  CHARACTER (len=*), INTENT(in) :: coordinate_type
394  TYPE (signal_pointer), DIMENSION(:), INTENT(inout) :: signals
395  INTEGER, INTENT(inout) :: signals_created
396  REAL (rprec), DIMENSION(:), INTENT(in) :: observed
397  REAL (rprec), DIMENSION(:), INTENT(in) :: sigma
398  REAL (rprec), DIMENSION(:), INTENT(in) :: weight
399  INTEGER, INTENT(inout) :: first_index
400  LOGICAL, INTENT(in) :: in_degrees
401  LOGICAL, INTENT(in) :: is_ratio
402 
403 ! local variables
404  class(mse_class), POINTER :: mse_obj
405  REAL (rprec), DIMENSION(3) :: xcart
406  REAL (rprec), DIMENSION(3) :: view_start
407  REAL (rprec), DIMENSION(3) :: view_end
408  REAL (rprec), DIMENSION(3) :: beam_start
409  REAL (rprec), DIMENSION(3) :: beam_end
410  CHARACTER (len=data_short_name_length) :: point_name
411  CHARACTER (len=signal_dot_line_len) :: line
412  REAL (rprec) :: start_time
413 
414 ! Start of executable code
415  start_time = profiler_get_start_time()
416 
417 ! Get the position and name of the point.
418  CALL signal_dot_parse_chord(mse_dot_file_ref, coordinate_type, &
419  & point_name, xcart)
420 
421 ! Get the start and end positons of the viewing chord.
422  view_start = signal_dot_parse_3_real(mse_dot_file_ref, &
423  & 'Failed to parse view ' // &
424  & 'start position.')
425  view_end = signal_dot_parse_3_real(mse_dot_file_ref, &
426  & 'Failed to parse view ' // &
427  & 'end position.')
428 
429 ! Get the start and end positons of the beam chord.
430  view_start = signal_dot_parse_3_real(mse_dot_file_ref, &
431  & 'Failed to parse beam ' // &
432  & 'start position.')
433  view_end = signal_dot_parse_3_real(mse_dot_file_ref, &
434  & 'Failed to parse beam ' // &
435  & 'end position.')
436 
437 ! Convert Coordinates if necessay.
438  IF (trim(coordinate_type) .eq. 'RPhiDegZ') THEN
439  view_start(2) = view_start(2)*degree ! Convert from degrees to radians.
440  view_start = cyl_to_cart(view_start)
441  view_end(2) = view_end(2)*degree ! Convert from degrees to radians.
442  view_end = cyl_to_cart(view_end)
443 
444  beam_start(2) = beam_start(2)*degree ! Convert from degrees to radians.
445  beam_start = cyl_to_cart(beam_start)
446  beam_end(2) = beam_end(2)*degree ! Convert from degrees to radians.
447  view_end = cyl_to_cart(beam_end)
448  END IF
449 
450  mse_obj => mse_class(xcart, view_start, view_end, beam_start, &
451  & beam_end, in_degrees, is_ratio)
452 
453  CALL signal_construct(mse_obj, point_name, point_name, 'arb', & &
454  & observed(signals_created + 1), sigma(signals_created + 1), &
455  & weight(signals_created + 1), &
456  & v3fit_input_find_scale_index(signals_created + 1), &
457  & v3fit_input_find_offset_index(signals_created + 1))
458 
459  signals(signals_created + 1)%p => mse_obj
460 
461  signals_created = signals_created + 1
462 
463 ! At lease one mse signal was made. Set the first index. This should only be
464 ! run once.
465  IF (first_index .eq. -1) THEN
466  first_index = signals_created
467  END IF
468 
469  CALL profiler_set_stop_time('mse_dot_parse_vec', start_time)
470 
471  END SUBROUTINE
472 
473 !-------------------------------------------------------------------------------
497 !-------------------------------------------------------------------------------
498  SUBROUTINE mse_dot_parse_ang(mse_dot_file_ref, coordinate_type, &
499  & signals, signals_created, &
500  & observed, sigma, weight, &
501  & first_index, in_degrees1, &
502  & in_degrees2, is_ratio)
503  USE mse
504  USE v3fit_input, only: v3fit_max_diagnostics, &
507  USE v3_utilities, only: err_fatal
509 
510  IMPLICIT NONE
511 
512 ! Declare Arguments
513  TYPE (signal_dot_file), INTENT(inout) :: mse_dot_file_ref
514  CHARACTER (len=*), INTENT(in) :: coordinate_type
515  TYPE (signal_pointer), DIMENSION(:), INTENT(inout) :: signals
516  INTEGER, INTENT(inout) :: signals_created
517  REAL (rprec), DIMENSION(:), INTENT(in) :: observed
518  REAL (rprec), DIMENSION(:), INTENT(in) :: sigma
519  REAL (rprec), DIMENSION(:), INTENT(in) :: weight
520  INTEGER, INTENT(inout) :: first_index
521  LOGICAL, INTENT(in) :: in_degrees1
522  LOGICAL, INTENT(in) :: in_degrees2
523  LOGICAL, INTENT(in) :: is_ratio
524 
525 ! local variables
526  class(mse_class), POINTER :: mse_obj
527  REAL (rprec), DIMENSION(3) :: xcart
528  REAL (rprec), DIMENSION(2) :: t_angles
529  REAL (rprec), DIMENSION(2) :: h_angles
530  CHARACTER (len=data_short_name_length) :: point_name
531  CHARACTER (len=signal_dot_line_len) :: line
532  REAL (rprec) :: start_time
533 
534 ! Start of executable code
535  start_time = profiler_get_start_time()
536 
537 ! Get the position and name of the point.
538  CALL signal_dot_parse_chord(mse_dot_file_ref, coordinate_type, &
539  & point_name, xcart)
540 
541 ! Get the alpha and omega.
542  t_angles = signal_dot_parse_2_real(mse_dot_file_ref, &
543  & 'Failed to parse angles ' // &
544  & 'to toroidal')
545 
546 ! Get the delta and theta.
547  h_angles = signal_dot_parse_2_real(mse_dot_file_ref, &
548  & 'Failed to parse angles ' // &
549  & 'to horizontal')
550 
551 ! Convert Coordinates if necessay.
552  IF (in_degrees1) THEN
553  t_angles = t_angles*degree
554  h_angles = h_angles*degree
555  END IF
556 
557  mse_obj => mse_class(xcart, t_angles(1), t_angles(2), h_angles(1), &
558  & h_angles(2), in_degrees2, is_ratio)
559 
560  CALL signal_construct(mse_obj, point_name, point_name, 'arb', &
561  & observed(signals_created + 1), &
562  & sigma(signals_created + 1), weight(signals_created + 1), &
563  & v3fit_input_find_scale_index(signals_created + 1), &
564  & v3fit_input_find_offset_index(signals_created + 1))
565 
566  signals(signals_created + 1)%p => mse_obj
567 
568  signals_created = signals_created + 1
569 
570 ! At lease one mse signal was made. Set the first index. This should only be
571 ! run once.
572  IF (first_index .eq. -1) THEN
573  first_index = signals_created
574  END IF
575 
576  CALL profiler_set_stop_time('mse_dot_parse_ang', start_time)
577 
578  END SUBROUTINE
579 
580  END MODULE
coordinate_utilities
Module is part of the LIBSTELL. This modules containes code to convert from different coordinate syst...
Definition: coordinate_utilities.f:12
v3fit_input::v3fit_max_diagnostics
integer, parameter v3fit_max_diagnostics
Maximum number of diagnostic signals.
Definition: v3fit_input.f:582
mse_dot
Module for opening and reading a 'mse.' file. The file format for these files are documented in Motio...
Definition: mse_dot.f:129
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
mse_dot::mse_dot_read
subroutine mse_dot_read(mse_file, signals, signals_created, observed, sigma, weight, first_index)
Read an motional stark effect diagnostic dot file.
Definition: mse_dot.f:159
signal_dot::signal_dot_parse_3_real
real(rprec) function, dimension(3) signal_dot_parse_3_real(signal_dot_file_ref, message)
Parse a three reals from a diagnostic dot file.
Definition: signal_dot.f:292
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
mse_dot::mse_dot_parse_vec
subroutine mse_dot_parse_vec(mse_dot_file_ref, coordinate_type, signals, signals_created, observed, sigma, weight, first_index, in_degrees, is_ratio)
Parse motional stark effect diagnostic point defined as a vector.
Definition: mse_dot.f:382
coordinate_utilities::cyl_to_cart
pure real(rprec) function, dimension(3), public cyl_to_cart(cyl)
Convert a point from cylindical coordinates to cartesian coordinates.
Definition: coordinate_utilities.f:67
data_parameters
This modules contains parameters used by equilibrium models.
Definition: data_parameters.f:10
mse::mse_class
Base class representing a mse signal.
Definition: mse.f:42
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
mse
Implements motional stark effect diagnostic. Defines the base class of the type mse_class.
Definition: mse.f:14
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
signal_dot::signal_dot_parse_2_real
real(rprec) function, dimension(2) signal_dot_parse_2_real(signal_dot_file_ref, message)
Parse a two reals from a diagnostic dot file.
Definition: signal_dot.f:251
mse_dot::mse_dot_parse_ang
subroutine mse_dot_parse_ang(mse_dot_file_ref, coordinate_type, signals, signals_created, observed, sigma, weight, first_index, in_degrees1, in_degrees2, is_ratio)
Parse motional stark effect diagnostic point defined as angles.
Definition: mse_dot.f:503