|
V3FIT
|
Go to the documentation of this file.
25 CHARACTER (len=*),
PARAMETER ::
nc_r0 =
'r0'
27 CHARACTER (len=*),
PARAMETER ::
nc_dr =
'dr'
29 CHARACTER (len=*),
PARAMETER ::
nc_z0 =
'z0'
31 CHARACTER (len=*),
PARAMETER ::
nc_dz =
'dz'
49 REAL (rprec),
DIMENSION(:,:,:),
POINTER :: grid => null()
51 REAL (rprec),
DIMENSION(:),
POINTER :: rgrid => null()
53 REAL (rprec),
DIMENSION(:),
POINTER :: zgrid => null()
96 CHARACTER (len=*),
INTENT(in) :: lgrid_file
97 LOGICAL,
INTENT(in) :: on_edge
106 INTEGER,
DIMENSION(3) :: dim_lengths
108 REAL (rprec) :: start_time
115 CALL cdf_open(lgrid_iou, trim(lgrid_file),
'r', status)
116 CALL assert_eq(0, status,
'limiter_grid_construct: ' //
117 &
'failed to open ', trim(lgrid_file))
119 CALL cdf_read(lgrid_iou,
nc_r0, r0)
120 CALL cdf_read(lgrid_iou,
nc_dr, dr)
121 CALL cdf_read(lgrid_iou,
nc_z0, z0)
122 CALL cdf_read(lgrid_iou,
nc_dz, dz)
136 CALL cdf_close(lgrid_iou)
139 DO i = 1, dim_lengths(1)
143 DO i = 1, dim_lengths(2)
164 TYPE (limiter_grid_class),
POINTER :: this
167 IF (
ASSOCIATED(this%phi))
THEN
172 IF (
ASSOCIATED(this%grid))
THEN
173 DEALLOCATE(this%grid)
177 IF (
ASSOCIATED(this%rgrid))
THEN
178 DEALLOCATE(this%rgrid)
182 IF (
ASSOCIATED(this%zgrid))
THEN
183 DEALLOCATE(this%zgrid)
204 & r, z, rphiz_at_max)
212 INTEGER,
INTENT(in) :: num_theta
213 INTEGER,
INTENT(in) :: phi_index
214 REAL (rprec),
DIMENSION(:),
INTENT(in) :: r
215 REAL (rprec),
DIMENSION(:),
INTENT(in) :: z
216 REAL (rprec),
DIMENSION(3),
INTENT(out) :: rphiz_at_max
221 REAL (rprec),
DIMENSION(:),
ALLOCATABLE :: fval
222 REAL (rprec) :: start_time
230 ALLOCATE(fval(num_theta))
236 & this%grid(:,:,phi_index), fval)
238 index = maxloc(fval, 1)
241 rphiz_at_max = (/ r(index), this%phi(phi_index), z(index) /)
270 REAL (rprec) :: start_time
276 & trim(this%limiter_class%get_type()) //
'grid'
real(rprec) function limiter_grid_get_max_fval(this, num_theta, phi_index, r, z, rphiz_at_max)
Calculates the maximum value of the grid function.
Defines functions for measuring an tabulating performance of function and subroutine calls....
character(len=data_name_length) function limiter_grid_get_type(this)
Gets a discription of the limiter grid type.
character(len= *), parameter nc_dz
NETCDF z grid spacing.
Base class representing a limiter signal.
type(bivariate_type) function, pointer bivariate_construct(ns, nu)
Construct a bivariate_type object.
An object containing persistent data for the bivariate interpolation.
character(len= *), parameter nc_r0
NETCDF r grid start.
subroutine bivariate_destruct(this)
Deconstruct a bivariate_type object.
Umbrella module avoid multiple inlcudes of the mpif.h header.
Interface for the setting of bivariate_type types either using bivariate_set_grids_1d or bivariate_se...
character(len= *), parameter nc_phi_angles
NETCDF grid phi angles.
real(rprec) function profiler_get_start_time()
Gets the start time of profiled function.
character(len= *), parameter nc_z0
NETCDF z grid start.
Base class representing a limiter signal.
Defines the base class of the type limiter_grid_class.
subroutine limiter_grid_destruct(this)
Deconstruct a limiter_grid_class object.
character(len= *), parameter nc_dr
NETCDF r grid spacing.
This modules contains parameters used by equilibrium models.
subroutine bivariate_get_4pt(this, resp_rz, resp_su)
Interpolate points on to responce function grid.
subroutine profiler_set_stop_time(symbol_name, start_time)
Gets the end time of profiled function.
Defines the base class of the type limiter_class.
This modules contains routines for interpolating points inside a grid. This was originally written by...
character(len= *), parameter nc_iso_grids
NETCDF grid iso surfaces.
class(limiter_grid_class) function, pointer limiter_grid_construct(lgrid_file, on_edge)
Construct a limiter_grid_class.