V3FIT
extcurz.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 !
13 !*******************************************************************************
14 
15  MODULE extcurz
16 
17  USE stel_kinds, only: rprec
18  USE mpi_inc
19  USE profiler
20  USE signal
21 
22  IMPLICIT NONE
23 
24 !*******************************************************************************
25 ! DERIVED-TYPE DECLARATIONS
26 ! 1) extcurz base class
27 !
28 !*******************************************************************************
29 !-------------------------------------------------------------------------------
34 !-------------------------------------------------------------------------------
35  TYPE, EXTENDS(signal_class) :: extcurz_class
37  REAL (rprec) :: r
39  REAL (rprec) :: theta
40  CONTAINS
41  PROCEDURE :: &
42  & get_modeled_signal_last => extcurz_get_modeled_signal
43  PROCEDURE :: get_type => extcurz_get_type
44  final :: extcurz_destruct
45  END TYPE extcurz_class
46 
47 !*******************************************************************************
48 ! INTERFACE BLOCKS
49 !*******************************************************************************
50 !-------------------------------------------------------------------------------
53 !-------------------------------------------------------------------------------
54  INTERFACE extcurz_class
55  MODULE PROCEDURE extcurz_construct
56  END INTERFACE
57 
58  CONTAINS
59 !*******************************************************************************
60 ! CONSTRUCTION SUBROUTINES
61 !*******************************************************************************
62 !-------------------------------------------------------------------------------
70 !-------------------------------------------------------------------------------
71  FUNCTION extcurz_construct(r, theta)
72 
73  IMPLICIT NONE
74 
75 ! Declare Arguments
76  class(extcurz_class), POINTER :: extcurz_construct
77  REAL(rprec), INTENT(in) :: r
78  REAL(rprec), INTENT(in) :: theta
79 
80 ! local variables
81  REAL (rprec) :: start_time
82 
83 ! Start of executable code
84  start_time = profiler_get_start_time()
85 
86  ALLOCATE(extcurz_construct)
87  extcurz_construct%r = r
88  extcurz_construct%theta = theta
89 
90  CALL profiler_set_stop_time('extcurz_construct', start_time)
91 
92  END FUNCTION
93 
94 !*******************************************************************************
95 ! DESTRUCTION SUBROUTINES
96 !*******************************************************************************
97 !-------------------------------------------------------------------------------
103 !-------------------------------------------------------------------------------
104  SUBROUTINE extcurz_destruct(this)
105 
106  IMPLICIT NONE
107 
108 ! Declare Arguments
109  TYPE (extcurz_class), INTENT(inout) :: this
110 
111 ! Start of executable code
112  this%r = 0.0
113  this%theta = 0.0
114 
115  END SUBROUTINE
116 
117 !*******************************************************************************
118 ! GETTER SUBROUTINES
119 !*******************************************************************************
120 !-------------------------------------------------------------------------------
132 !-------------------------------------------------------------------------------
133  FUNCTION extcurz_get_modeled_signal(this, a_model, sigma, &
134  & last_value)
135  USE model
136  USE stel_constants, only: mu0
137 
138  IMPLICIT NONE
139 
140 ! Declare Arguments
141  REAL (rprec), DIMENSION(4) :: extcurz_get_modeled_signal
142  class(extcurz_class), INTENT(inout) :: this
143  TYPE (model_class), POINTER :: a_model
144  REAL (rprec), DIMENSION(4), INTENT(out) :: sigma
145  REAL (rprec), DIMENSION(4), INTENT(in) :: last_value
146 
147 ! local variables
148  REAL (rprec) :: start_time
149 
150 ! Start of executable code
151  start_time = profiler_get_start_time()
152 
153  sigma = 0
154 
155  IF (btest(a_model%state_flags, model_state_vmec_flag) .or. &
156  & btest(a_model%state_flags, model_state_siesta_flag) .or. &
157  & btest(a_model%state_flags, model_state_signal_flag)) THEN
159  & equilibrium_get_int_b_dphi(a_model%equilibrium, this%r, &
160  & this%theta)/mu0
161 
162  CALL this%scale_and_offset(a_model, &
164  ELSE
165  extcurz_get_modeled_signal = last_value
166  END IF
167 
168  CALL profiler_set_stop_time('extcurz_get_modeled_signal', &
169  & start_time)
170 
171  END FUNCTION
172 
173 !-------------------------------------------------------------------------------
180 !-------------------------------------------------------------------------------
181  FUNCTION extcurz_get_type(this)
183 
184  IMPLICIT NONE
185 
186 ! Declare Arguments
187  CHARACTER (len=data_name_length) :: extcurz_get_type
188  class(extcurz_class), INTENT(in) :: this
189 
190 ! local variables
191  REAL (rprec) :: start_time
192 
193 ! Start of executable code
194  start_time = profiler_get_start_time()
195 
196  extcurz_get_type = 'extcur'
197 
198  CALL profiler_set_stop_time('extcurz_get_type', start_time)
199 
200  END FUNCTION
201 
202  END MODULE
extcurz
Represents a signal obtained by integrating around the magnetic field to get the current enclosed in ...
Definition: extcurz.f:15
profiler
Defines functions for measuring an tabulating performance of function and subroutine calls....
Definition: profiler.f:13
model
Defines the base class of the type model_class. The model contains information not specific to the eq...
Definition: model.f:59
mpi_inc
Umbrella module avoid multiple inlcudes of the mpif.h header.
Definition: mpi_inc.f:11
extcurz::extcurz_destruct
subroutine extcurz_destruct(this)
Deconstruct a extcurz_class object.
Definition: extcurz.f:105
extcurz::extcurz_construct
class(extcurz_class) function, pointer extcurz_construct(r, theta)
Construct a extcurz_class object measureing temperature.
Definition: extcurz.f:72
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
extcurz::extcurz_get_modeled_signal
real(rprec) function, dimension(4) extcurz_get_modeled_signal(this, a_model, sigma, last_value)
Calculates the modeled signal.
Definition: extcurz.f:135
data_parameters
This modules contains parameters used by equilibrium models.
Definition: data_parameters.f:10
extcurz::extcurz_class
Base class representing a external Z currents enclosed by an inegration loop.
Definition: extcurz.f:35
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
extcurz::extcurz_get_type
character(len=data_name_length) function extcurz_get_type(this)
Gets a discription of the extcurz type.
Definition: extcurz.f:182
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