V3FIT
mse.f
Go to the documentation of this file.
1 !*******************************************************************************
4 !
5 ! Note separating the Doxygen comment block here so detailed decription is
6 ! found in the Module not the file.
7 !
12 !*******************************************************************************
13 
14  MODULE mse
15 
16  USE stel_kinds, only: rprec, dp
18  USE profiler
19  USE mpi_inc
20  USE signal
21 
22  IMPLICIT NONE
23 
24 !*******************************************************************************
25 ! mse module parameters
26 !*******************************************************************************
28  INTEGER, PARAMETER :: mse_degrees_flag = 1
30  INTEGER, PARAMETER :: mse_ratio_flag = 2
31 
32 !*******************************************************************************
33 ! DERIVED-TYPE DECLARATIONS
34 ! 1) mse base class
35 !
36 !*******************************************************************************
37 !-------------------------------------------------------------------------------
41 !-------------------------------------------------------------------------------
42  TYPE, EXTENDS(signal_class) :: mse_class
44  REAL (rprec), DIMENSION(3) :: point
45 
47  REAL (rprec) :: alpha
49  REAL (rprec) :: omega
51  REAL (rprec) :: delta
53  REAL (rprec) :: theta
54 
56  INTEGER :: flags
57  CONTAINS
58  PROCEDURE :: &
59  & get_modeled_signal_last => mse_get_modeled_signal
60  PROCEDURE :: &
61  & get_type => mse_get_type
62  PROCEDURE :: get_header => mse_get_header
63  PROCEDURE, PRIVATE :: &
64  & angle_to_bt_proj => mse_angle_to_bt_proj
65  final :: mse_destruct
66  END TYPE
67 
68 !*******************************************************************************
69 ! INTERFACE BLOCKS
70 !*******************************************************************************
71 !-------------------------------------------------------------------------------
74 !-------------------------------------------------------------------------------
75  INTERFACE mse_class
76  MODULE PROCEDURE mse_construct_vec, &
78  END INTERFACE
79 
81 
82  CONTAINS
83 !*******************************************************************************
84 ! CONSTRUCTION SUBROUTINES
85 !*******************************************************************************
86 !-------------------------------------------------------------------------------
101 !-------------------------------------------------------------------------------
102  FUNCTION mse_construct_vec(point, view_start, view_end, &
103  & beam_start, beam_end, in_degrees, &
104  & is_ratio)
105 
106  IMPLICIT NONE
107 
108 ! Declare Arguments
109  class(mse_class), POINTER :: mse_construct_vec
110  REAL (rprec), DIMENSION(3), INTENT(in) :: point
111  REAL (rprec), DIMENSION(3), INTENT(in) :: view_start
112  REAL (rprec), DIMENSION(3), INTENT(in) :: view_end
113  REAL (rprec), DIMENSION(3), INTENT(in) :: beam_start
114  REAL (rprec), DIMENSION(3), INTENT(in) :: beam_end
115  LOGICAL, INTENT(in) :: in_degrees
116  LOGICAL, INTENT(in) :: is_ratio
117 
118 ! local variables
119  REAL (rprec) :: start_time
120 
121 ! Start of executable code
122  start_time = profiler_get_start_time()
123 
124  ALLOCATE(mse_construct_vec)
125 
126  mse_construct_vec%flags = 0
127  IF (in_degrees) THEN
128  mse_construct_vec%flags = ibset(mse_construct_vec%flags, &
130  END IF
131  IF (is_ratio) THEN
132  mse_construct_vec%flags = ibset(mse_construct_vec%flags, &
133  & mse_ratio_flag)
134  END IF
135 
136  mse_construct_vec%point = point
137 
138 ! Get the angles with respect to the toroidal field component.
139 ! The mse alpha is defined so that 0 points in the negative torodial direction
140 ! and 90 points in the negative radial direction. So this needs to be PI minus
141 ! the angle obtained from the dotproduct.
142  mse_construct_vec%alpha = pi - &
143  & mse_construct_vec%angle_to_bt_proj(beam_end - beam_start)
144  mse_construct_vec%omega = &
145  & mse_construct_vec%angle_to_bt_proj(view_end - view_start)
146 
147 ! Get the angles with respect to the horizontal.
148 ! The mse delta is defined so that 90 points in the negative z direction. So
149 ! this needs to be the negation of the angle obtained from the dotproduct.
150  mse_construct_vec%delta = &
151  & -mse_angle_to_horizontal(beam_end - beam_start)
152  mse_construct_vec%theta = &
153  & mse_angle_to_horizontal(view_end - view_start)
154 
155  CALL profiler_set_stop_time('mse_construct_vec', start_time)
156 
157  END FUNCTION
158 
159 !-------------------------------------------------------------------------------
176 !-------------------------------------------------------------------------------
177  FUNCTION mse_construct_rad(point, alpha, omega, delta, theta, &
178  & in_degrees, is_ratio)
179 
180  IMPLICIT NONE
181 
182 ! Declare Arguments
183  class(mse_class), POINTER :: mse_construct_rad
184  REAL (rprec), DIMENSION(3), INTENT(in) :: point
185  REAL (rprec), INTENT(in) :: alpha
186  REAL (rprec), INTENT(in) :: omega
187  REAL (rprec), INTENT(in) :: delta
188  REAL (rprec), INTENT(in) :: theta
189  LOGICAL, INTENT(in) :: in_degrees
190  LOGICAL, INTENT(in) :: is_ratio
191 
192 ! local variables
193  REAL (rprec) :: start_time
194 
195 ! Start of executable code
196  start_time = profiler_get_start_time()
197 
198  ALLOCATE(mse_construct_rad)
199 
200  mse_construct_rad%flags = 0
201  IF (in_degrees) THEN
202  mse_construct_rad%flags = ibset(mse_construct_rad%flags, &
204  END IF
205  IF (is_ratio) THEN
206  mse_construct_rad%flags = ibset(mse_construct_rad%flags, &
207  & mse_ratio_flag)
208  END IF
209 
210  mse_construct_rad%point = point
211 
212 ! Get the angles with respect to the toroidal field component.
213  mse_construct_rad%alpha = alpha
214  mse_construct_rad%omega = omega
215  mse_construct_rad%delta = delta
216  mse_construct_rad%theta = theta
217 
218  CALL profiler_set_stop_time('mse_construct_rad', start_time)
219 
220  END FUNCTION
221 
222 !*******************************************************************************
223 ! DESTRUCTION SUBROUTINES
224 !*******************************************************************************
225 !-------------------------------------------------------------------------------
231 !-------------------------------------------------------------------------------
232  SUBROUTINE mse_destruct(this)
233 
234  IMPLICIT NONE
235 
236 ! Declare Arguments
237  TYPE (mse_class), INTENT(inout) :: this
238 
239 ! Start of executable code
240  this%point = 0.0
241  this%alpha = 0.0
242  this%omega = 0.0
243  this%delta = 0.0
244  this%theta = 0.0
245  this%flags = 0
246 
247  END SUBROUTINE
248 
249 !*******************************************************************************
250 ! GETTER SUBROUTINES
251 !*******************************************************************************
252 !-------------------------------------------------------------------------------
289 !-------------------------------------------------------------------------------
290  FUNCTION mse_get_modeled_signal(this, a_model, sigma, last_value)
291  USE model
292 
293  IMPLICIT NONE
294 
295 ! Declare Arguments
296  REAL (rprec), DIMENSION(4) :: mse_get_modeled_signal
297  CLASS (mse_class), INTENT(inout) :: this
298  TYPE (model_class), POINTER :: a_model
299  REAL (rprec), DIMENSION(4), INTENT(out) :: sigma
300  REAL (rprec), DIMENSION(4), INTENT(in) :: last_value
301 
302 ! local variables
303  REAL (rprec), DIMENSION(3) :: b_cyl
304  REAL (rprec) :: start_time
305 
306 ! Start of executable code
307  start_time = profiler_get_start_time()
308 
309  sigma = 0.0
310 
311  IF (btest(a_model%state_flags, model_state_vmec_flag) .or. &
312  & btest(a_model%state_flags, model_state_siesta_flag) .or. &
313  & btest(a_model%state_flags, model_state_shift_flag) .or. &
314  & btest(a_model%state_flags, model_state_signal_flag)) THEN
315 
316 ! Get the magnetic field vector.
317  b_cyl = equilibrium_get_b_vec(a_model%equilibrium, this%point, &
318  & .true.)
319 
321  & -(b_cyl(3)*cos(this%delta)*cos(this%omega + this%alpha) + &
322  & sin(this%delta)*(b_cyl(1)*sin(this%omega) - &
323  & b_cyl(2)*cos(this%omega)))
324 
326  & -b_cyl(3)*sin(this%theta)*cos(this%delta)* &
327  & sin(this%omega + this%alpha) &
328  & + sin(this%theta)*sin(this%delta)* &
329  & (b_cyl(2)*sin(this%omega) + b_cyl(1)*cos(this%omega)) &
330  & + cos(this%theta)*cos(this%delta)* &
331  & (b_cyl(1)*cos(this%alpha) - b_cyl(2)*sin(this%alpha))
332 
335 
336  IF (btest(this%flags, mse_ratio_flag)) THEN
338  ELSE
341 
342  IF (btest(this%flags, mse_degrees_flag)) THEN
344  & / degree
345  END IF
346  END IF
347 
348  CALL this%scale_and_offset(a_model, mse_get_modeled_signal(1))
349  ELSE
350  mse_get_modeled_signal = last_value
351  END IF
352 
353  CALL profiler_set_stop_time('mse_get_modeled_signal', start_time)
354 
355  END FUNCTION
356 
357 !-------------------------------------------------------------------------------
364 !-------------------------------------------------------------------------------
365  FUNCTION mse_get_type(this)
367 
368  IMPLICIT NONE
369 
370 ! Declare Arguments
371  CHARACTER (len=data_name_length) :: mse_get_type
372  CLASS (mse_class), INTENT(in) :: this
373 
374 ! local variables
375  REAL (rprec) :: start_time
376 
377 ! Start of executable code
378  start_time = profiler_get_start_time()
379 
380  mse_get_type = 'mse'
381 
382  CALL profiler_set_stop_time('mse_get_type', start_time)
383 
384  END FUNCTION
385 
386 !-------------------------------------------------------------------------------
395 !-------------------------------------------------------------------------------
396  SUBROUTINE mse_get_header(this, header)
398 
399  IMPLICIT NONE
400 
401 ! Declare Arguments
402  class(mse_class), INTENT(in) :: this
403  CHARACTER (len=data_name_length), DIMENSION(7), INTENT(inout) :: &
404  & header
405 
406 ! local variables
407  REAL (rprec) :: start_time
408 
409 ! Start of executable code
410  start_time = profiler_get_start_time()
411 
412  header(1) = 'e_h'
413  header(2) = 'e_v'
414  header(3) = 'ratio'
415 
416  header(4) = 'model_sig(1)'
417  header(5) = 'model_sig(2)'
418  header(6) = 'model_sig(3)'
419  header(7) = 'model_sig(4)'
420 
421  CALL profiler_set_stop_time('mse_get_header', start_time)
422 
423  END SUBROUTINE
424 
425 !*******************************************************************************
426 ! PRIVATE
427 !*******************************************************************************
428 !-------------------------------------------------------------------------------
445 !-------------------------------------------------------------------------------
446  FUNCTION mse_angle_to_bt_proj(this, vec)
447 
448  IMPLICIT NONE
449 
450 ! Declare Arguments
451  REAL (rprec) :: mse_angle_to_bt_proj
452  CLASS (mse_class), INTENT(in) :: this
453  REAL (rprec), DIMENSION(3) :: vec
454 
455 ! local variables
456  REAL (rprec), DIMENSION(2) :: temp_vec
457  REAL (rprec), DIMENSION(2) :: norm_vec
458  REAL (rprec) :: start_time
459 
460 ! Start of executable code
461  start_time = profiler_get_start_time()
462 
463 ! Unit vector in the direction of
464  temp_vec = (/ -this%point(2), this%point(1) /) &
465  & / sqrt(dot_product(this%point(1:2), this%point(1:2)))
466 
467 ! Compute the angle.
468  norm_vec = vec(1:2)/sqrt(dot_product(vec(1:2), vec(1:2)))
469  mse_angle_to_bt_proj = acos(dot_product(temp_vec, norm_vec))
470 
471  CALL profiler_set_stop_time('mse_angle_to_bt_proj', start_time)
472 
473  END FUNCTION
474 
475 !-------------------------------------------------------------------------------
485 !-------------------------------------------------------------------------------
486  FUNCTION mse_angle_to_horizontal(vec)
487 
488  IMPLICIT NONE
489 
490 ! Declare Arguments
491  REAL (rprec) :: mse_angle_to_horizontal
492  REAL (rprec), DIMENSION(3) :: vec
493 
494 ! local variables
495  REAL (rprec) :: h
496  REAL (rprec) :: start_time
497 
498 ! Start of executable code
499  start_time = profiler_get_start_time()
500 
501  h = sqrt(dot_product(vec, vec))
502  mse_angle_to_horizontal = asin(vec(3)/h)
504 
505  CALL profiler_set_stop_time('mse_angle_to_horizontal', start_time)
506 
507  END FUNCTION
508 
509  END MODULE
profiler
Defines functions for measuring an tabulating performance of function and subroutine calls....
Definition: profiler.f:13
coordinate_utilities
Module is part of the LIBSTELL. This modules containes code to convert from different coordinate syst...
Definition: coordinate_utilities.f:12
mse::mse_angle_to_horizontal
real(rprec) function, private mse_angle_to_horizontal(vec)
Computes the angle with respect to horizontal.
Definition: mse.f:487
model
Defines the base class of the type model_class. The model contains information not specific to the eq...
Definition: model.f:59
mse::mse_get_modeled_signal
real(rprec) function, dimension(4) mse_get_modeled_signal(this, a_model, sigma, last_value)
Calculates the modeled signal.
Definition: mse.f:291
mpi_inc
Umbrella module avoid multiple inlcudes of the mpif.h header.
Definition: mpi_inc.f:11
mse::mse_destruct
subroutine mse_destruct(this)
Deconstruct a mse_class object.
Definition: mse.f:233
mse::mse_ratio_flag
integer, parameter mse_ratio_flag
Bit position for the force coil response flag.
Definition: mse.f:30
profiler::profiler_get_start_time
real(rprec) function profiler_get_start_time()
Gets the start time of profiled function.
Definition: profiler.f:194
model::model_class
Base class representing a model.
Definition: model.f:141
mse::mse_angle_to_bt_proj
real(rprec) function, private mse_angle_to_bt_proj(this, vec)
Computes the angle with respect to toroidal field.
Definition: mse.f:447
mse::mse_construct_rad
class(mse_class) function, pointer mse_construct_rad(point, alpha, omega, delta, theta, in_degrees, is_ratio)
Construct a mse_class object representing a motional stark effect diagnostic.
Definition: mse.f:179
mse::mse_construct_vec
class(mse_class) function, pointer mse_construct_vec(point, view_start, view_end, beam_start, beam_end, in_degrees, is_ratio)
Construct a mse_class object representing a motional stark effect diagnostic.
Definition: mse.f:105
mse::mse_get_type
character(len=data_name_length) function mse_get_type(this)
Gets a discription of the mse type.
Definition: mse.f:366
mse::mse_degrees_flag
integer, parameter mse_degrees_flag
Bit position for the use coil response flag.
Definition: mse.f:28
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
mse::mse_get_header
subroutine mse_get_header(this, header)
Gets a discription of the model and model sigma array indices.
Definition: mse.f:397
profiler::profiler_set_stop_time
subroutine profiler_set_stop_time(symbol_name, start_time)
Gets the end time of profiled function.
Definition: profiler.f:121
mse
Implements motional stark effect diagnostic. Defines the base class of the type mse_class.
Definition: mse.f:14
signal::signal_class
Base class representing a signal.
Definition: signal.f:33
signal
Defines the base class of the type signal_class.
Definition: signal.f:14