|
V3FIT
|
Go to the documentation of this file.
55 REAL (rprec) :: te_start = 0.0
57 REAL (rprec) :: te_step = 0.0
60 REAL (rprec),
DIMENSION(:,:),
POINTER :: emissivity => null()
91 CHARACTER (len=*),
INTENT(in) :: filename
94 REAL (rprec) :: start_time
97 INTEGER,
DIMENSION(2) :: dim_lengths
104 CALL cdf_open(iou, trim(filename),
'r', status)
105 CALL assert_eq(0, status,
'failed to open emission file')
110 CALL cdf_inquire(iou,
'emissivity', dim_lengths)
113 CALL cdf_read(iou,
'emissivity',
138 TYPE (emission_class),
POINTER :: this
141 IF (
ASSOCIATED(this%emissivity))
THEN
142 DEALLOCATE(this%emissivity)
143 this%emissivity => null()
173 REAL (rprec),
INTENT(in) :: te
174 REAL (rprec),
INTENT(in) :: ne
175 INTEGER,
INTENT(in) :: index
178 INTEGER :: i_low, i_high
179 REAL (rprec) :: w_low, w_high
181 REAL (rprec) :: start_time
187 IF (te .eq. 0.0)
THEN
197 num_temp =
SIZE(this%emissivity, 2)
199 IF (te .lt. this%te_start)
THEN
206 w_low = te/this%te_start
207 ELSE IF (te .gt. this%te_start + (num_temp - 1)*this%te_step)
THEN
214 i_low = (te - this%te_start)/this%te_step + 1
217 w_high = (te - this%te_start)/this%te_step + 1.0 - i_low
222 & + w_low*this%emissivity(index,i_low)
Defines functions for measuring an tabulating performance of function and subroutine calls....
subroutine emission_destruct(this)
Deconstruct a emission_class object.
Umbrella module avoid multiple inlcudes of the mpif.h header.
real(rprec) function profiler_get_start_time()
Gets the start time of profiled function.
type(emission_class) function, pointer emission_construct_netcdf(filename)
Construct a emission_class object.
real(rprec) function emission_get_emission(this, te, ne, index)
Gets the emission as a function of energy for a fixed temperature.
Base class representing the soft x-ray emission function.
subroutine profiler_set_stop_time(symbol_name, start_time)
Gets the end time of profiled function.
Defines the base class of the type emission_class. This contains the X-Ray emission as function of te...