V3FIT
emission.f
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
2 ! The @header, @table_section, @table_subsection, @item and @end_table commands
3 ! are custom defined commands in Doxygen.in. They are defined under ALIASES.
4 ! For the page created here, the 80 column limit is exceeded. Arguments of
5 ! aliases are separated by ','. If you intended ',' to be a string you must use
6 ! an escaped comma '\,'.
7 !
26 !*******************************************************************************
29 !
30 ! Note separating the Doxygen comment block here so detailed decription is
31 ! found in the Module not the file.
32 !
36 !*******************************************************************************
37 
38  MODULE emission
39  USE stel_kinds
40  USE profiler
41  USE mpi_inc
42 
43  IMPLICIT NONE
44 
45 !*******************************************************************************
46 ! DERIVED-TYPE DECLARATIONS
47 ! 1) emission class
48 !
49 !*******************************************************************************
50 !-------------------------------------------------------------------------------
52 !-------------------------------------------------------------------------------
55  REAL (rprec) :: te_start = 0.0
57  REAL (rprec) :: te_step = 0.0
58 
60  REAL (rprec), DIMENSION(:,:), POINTER :: emissivity => null()
61  END TYPE
62 
63 !*******************************************************************************
64 ! INTERFACE BLOCKS
65 !*******************************************************************************
67  MODULE PROCEDURE emission_construct_netcdf
68  END INTERFACE
69 
70  CONTAINS
71 !*******************************************************************************
72 ! CONSTRUCTION SUBROUTINES
73 !*******************************************************************************
74 !-------------------------------------------------------------------------------
82 !-------------------------------------------------------------------------------
83  FUNCTION emission_construct_netcdf(filename)
84  USE ezcdf
85  USE v3_utilities
86 
87  IMPLICIT NONE
88 
89 ! Declare Arguments
90  TYPE (emission_class), POINTER :: emission_construct_netcdf
91  CHARACTER (len=*), INTENT(in) :: filename
92 
93 ! local variables
94  REAL (rprec) :: start_time
95  INTEGER :: iou
96  INTEGER :: status
97  INTEGER, DIMENSION(2) :: dim_lengths
98 
99 ! Start of executable code
100  start_time = profiler_get_start_time()
101 
102  ALLOCATE(emission_construct_netcdf)
103 
104  CALL cdf_open(iou, trim(filename), 'r', status)
105  CALL assert_eq(0, status, 'failed to open emission file')
106 
107  CALL cdf_read(iou, 'te_start', emission_construct_netcdf%te_start)
108  CALL cdf_read(iou, 'te_step', emission_construct_netcdf%te_step)
109 
110  CALL cdf_inquire(iou, 'emissivity', dim_lengths)
111  ALLOCATE(emission_construct_netcdf%emissivity(dim_lengths(1), &
112  & dim_lengths(2)))
113  CALL cdf_read(iou, 'emissivity', &
114  & emission_construct_netcdf%emissivity)
115 
116  CALL cdf_close(iou)
117 
118  CALL profiler_set_stop_time('emission_construct_netcdf', &
119  & start_time)
120 
121  END FUNCTION
122 
123 !*******************************************************************************
124 ! DESTRUCTION SUBROUTINES
125 !*******************************************************************************
126 !-------------------------------------------------------------------------------
132 !-------------------------------------------------------------------------------
133  SUBROUTINE emission_destruct(this)
134 
135  IMPLICIT NONE
136 
137 ! Declare Arguments
138  TYPE (emission_class), POINTER :: this
139 
140 ! Start of executable code
141  IF (ASSOCIATED(this%emissivity)) THEN
142  DEALLOCATE(this%emissivity)
143  this%emissivity => null()
144  END IF
145 
146  DEALLOCATE(this)
147 
148  END SUBROUTINE
149 
150 !*******************************************************************************
151 ! GETTER SUBROUTINES
152 !*******************************************************************************
153 !-------------------------------------------------------------------------------
165 !-------------------------------------------------------------------------------
166  FUNCTION emission_get_emission(this, te, ne, index)
167 
168  IMPLICIT NONE
169 
170 ! Declare Arguments
171  REAL (rprec) :: emission_get_emission
172  TYPE (emission_class), INTENT(in) :: this
173  REAL (rprec), INTENT(in) :: te
174  REAL (rprec), INTENT(in) :: ne
175  INTEGER, INTENT(in) :: index
176 
177 ! local variables
178  INTEGER :: i_low, i_high
179  REAL (rprec) :: w_low, w_high
180  INTEGER :: num_temp
181  REAL (rprec) :: start_time
182 
183 ! Start of executable code
184  start_time = profiler_get_start_time()
185 
186 ! Avoid a divid by zero error.
187  IF (te .eq. 0.0) THEN
189  CALL profiler_set_stop_time('emission_get_emission', &
190  & start_time)
191  RETURN
192  END IF
193 
194 ! Determine the high and low indices for interpolating. If the temperature is
195 ! beyond the first or last temperature, linearly interpolate from the last two
196 ! temperatures.
197  num_temp = SIZE(this%emissivity, 2)
198 
199  IF (te .lt. this%te_start) THEN
200 ! Assume no emission at zero eV. Interpolate between zero and the first
201 ! temperature level.
202  i_low = 1
203  i_high = 2
204 
205  w_high = 0.0
206  w_low = te/this%te_start
207  ELSE IF (te .gt. this%te_start + (num_temp - 1)*this%te_step) THEN
208  i_high = num_temp
209  i_low = i_high - 1
210 
211  w_high = 1.0
212  w_low = 0.0
213  ELSE
214  i_low = (te - this%te_start)/this%te_step + 1
215  i_high = i_low + 1
216 
217  w_high = (te - this%te_start)/this%te_step + 1.0 - i_low
218  w_low = 1.0 - w_high
219  END IF
220 
221  emission_get_emission = w_high*this%emissivity(index,i_high) &
222  & + w_low*this%emissivity(index,i_low)
223 
224  emission_get_emission = ne*ne/sqrt(te)*max(emission_get_emission, &
225  & 0.0)
226 
227  CALL profiler_set_stop_time('emission_get_emission', start_time)
228 
229  END FUNCTION
230 
231  END MODULE
profiler
Defines functions for measuring an tabulating performance of function and subroutine calls....
Definition: profiler.f:13
emission::emission_destruct
subroutine emission_destruct(this)
Deconstruct a emission_class object.
Definition: emission.f:134
v3_utilities::assert_eq
Definition: v3_utilities.f:62
mpi_inc
Umbrella module avoid multiple inlcudes of the mpif.h header.
Definition: mpi_inc.f:11
profiler::profiler_get_start_time
real(rprec) function profiler_get_start_time()
Gets the start time of profiled function.
Definition: profiler.f:194
emission::emission_construct_netcdf
type(emission_class) function, pointer emission_construct_netcdf(filename)
Construct a emission_class object.
Definition: emission.f:84
emission::emission_construct
Definition: emission.f:66
emission::emission_get_emission
real(rprec) function emission_get_emission(this, te, ne, index)
Gets the emission as a function of energy for a fixed temperature.
Definition: emission.f:167
emission::emission_class
Base class representing the soft x-ray emission function.
Definition: emission.f:53
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
emission
Defines the base class of the type emission_class. This contains the X-Ray emission as function of te...
Definition: emission.f:38