|
V3FIT
|
Go to the documentation of this file.
16 USE stel_kinds,
only: rprec, dp
44 REAL (rprec),
DIMENSION(3) :: point
103 & beam_start, beam_end, in_degrees, &
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
119 REAL (rprec) :: start_time
178 & in_degrees, is_ratio)
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
193 REAL (rprec) :: start_time
237 TYPE (mse_class),
INTENT(inout) :: this
299 REAL (rprec),
DIMENSION(4),
INTENT(out) :: sigma
300 REAL (rprec),
DIMENSION(4),
INTENT(in) :: last_value
303 REAL (rprec),
DIMENSION(3) :: b_cyl
304 REAL (rprec) :: start_time
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
317 b_cyl = equilibrium_get_b_vec(a_model%equilibrium, this%point,
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)))
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))
375 REAL (rprec) :: start_time
403 CHARACTER (len=data_name_length),
DIMENSION(7),
INTENT(inout) ::
407 REAL (rprec) :: start_time
416 header(4) =
'model_sig(1)'
417 header(5) =
'model_sig(2)'
418 header(6) =
'model_sig(3)'
419 header(7) =
'model_sig(4)'
453 REAL (rprec),
DIMENSION(3) :: vec
456 REAL (rprec),
DIMENSION(2) :: temp_vec
457 REAL (rprec),
DIMENSION(2) :: norm_vec
458 REAL (rprec) :: start_time
464 temp_vec = (/ -this%point(2), this%point(1) /)
465 & / sqrt(dot_product(this%point(1:2), this%point(1:2)))
468 norm_vec = vec(1:2)/sqrt(dot_product(vec(1:2), vec(1:2)))
492 REAL (rprec),
DIMENSION(3) :: vec
496 REAL (rprec) :: start_time
501 h = sqrt(dot_product(vec, vec))
Defines functions for measuring an tabulating performance of function and subroutine calls....
Module is part of the LIBSTELL. This modules containes code to convert from different coordinate syst...
real(rprec) function, private mse_angle_to_horizontal(vec)
Computes the angle with respect to horizontal.
Defines the base class of the type model_class. The model contains information not specific to the eq...
real(rprec) function, dimension(4) mse_get_modeled_signal(this, a_model, sigma, last_value)
Calculates the modeled signal.
Umbrella module avoid multiple inlcudes of the mpif.h header.
subroutine mse_destruct(this)
Deconstruct a mse_class object.
integer, parameter mse_ratio_flag
Bit position for the force coil response flag.
real(rprec) function profiler_get_start_time()
Gets the start time of profiled function.
Base class representing a model.
real(rprec) function, private mse_angle_to_bt_proj(this, vec)
Computes the angle with respect to toroidal field.
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.
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.
character(len=data_name_length) function mse_get_type(this)
Gets a discription of the mse type.
integer, parameter mse_degrees_flag
Bit position for the use coil response flag.
This modules contains parameters used by equilibrium models.
Base class representing a mse signal.
subroutine mse_get_header(this, header)
Gets a discription of the model and model sigma array indices.
subroutine profiler_set_stop_time(symbol_name, start_time)
Gets the end time of profiled function.
Implements motional stark effect diagnostic. Defines the base class of the type mse_class.
Base class representing a signal.
Defines the base class of the type signal_class.