V3FIT
limiter_grid.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 !
11 !*******************************************************************************
12 
13  MODULE limiter_grid
14  USE stel_kinds
15  USE mpi_inc
16  USE profiler
17  USE limiter
18 
19  IMPLICIT NONE
20 
21 !*******************************************************************************
22 ! limiter_grid module parameters
23 !*******************************************************************************
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'
33  CHARACTER (len=*), PARAMETER :: nc_phi_angles = 'phi_angles'
35  CHARACTER (len=*), PARAMETER :: nc_iso_grids = 'iso_grids'
36 
37 !*******************************************************************************
38 ! DERIVED-TYPE DECLARATIONS
39 ! 1) limiter_grid base class
40 !
41 !*******************************************************************************
42 !-------------------------------------------------------------------------------
46 !-------------------------------------------------------------------------------
49  REAL (rprec), DIMENSION(:,:,:), POINTER :: grid => null()
51  REAL (rprec), DIMENSION(:), POINTER :: rgrid => null()
53  REAL (rprec), DIMENSION(:), POINTER :: zgrid => null()
54  CONTAINS
55  PROCEDURE :: &
56  & get_max_fval => limiter_grid_get_max_fval
57  PROCEDURE :: &
58  & get_type => limiter_grid_get_type
59  END TYPE
60 
61 !*******************************************************************************
62 ! INTERFACE BLOCKS
63 !*******************************************************************************
64 !-------------------------------------------------------------------------------
66 !-------------------------------------------------------------------------------
67  INTERFACE limiter_grid_class
68  MODULE PROCEDURE limiter_grid_construct
69  END INTERFACE
70 
71  CONTAINS
72 !*******************************************************************************
73 ! CONSTRUCTION SUBROUTINES
74 !*******************************************************************************
75 !-------------------------------------------------------------------------------
87 !-------------------------------------------------------------------------------
88  FUNCTION limiter_grid_construct(lgrid_file, on_edge)
89  USE ezcdf
90  USE v3_utilities
91 
92  IMPLICIT NONE
93 
94 ! Declare Arguments
96  CHARACTER (len=*), INTENT(in) :: lgrid_file
97  LOGICAL, INTENT(in) :: on_edge
98 
99 ! local variables
100  REAL (rprec) :: r0
101  REAL (rprec) :: dr
102  REAL (rprec) :: z0
103  REAL (rprec) :: dz
104  INTEGER :: lgrid_iou
105  INTEGER :: status
106  INTEGER, DIMENSION(3) :: dim_lengths
107  INTEGER :: i
108  REAL (rprec) :: start_time
109 
110 ! Start of executable code
111  start_time = profiler_get_start_time()
112 
113  ALLOCATE(limiter_grid_construct)
114 
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))
118 
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)
123 
124  CALL cdf_inquire(lgrid_iou, nc_phi_angles, dim_lengths)
125  ALLOCATE(limiter_grid_construct%phi(dim_lengths(1)))
126  CALL cdf_read(lgrid_iou, nc_phi_angles, &
128 
129  CALL cdf_inquire(lgrid_iou, nc_iso_grids, dim_lengths)
130  ALLOCATE(limiter_grid_construct%grid(dim_lengths(1), &
131  & dim_lengths(2), &
132  & dim_lengths(3)))
133  CALL cdf_read(lgrid_iou, nc_iso_grids, &
134  & limiter_grid_construct%grid)
135 
136  CALL cdf_close(lgrid_iou)
137 
138  ALLOCATE(limiter_grid_construct%rgrid(dim_lengths(1)))
139  DO i = 1, dim_lengths(1)
140  limiter_grid_construct%rgrid(i) = (i - 1)*dr + r0
141  END DO
142  ALLOCATE(limiter_grid_construct%zgrid(dim_lengths(2)))
143  DO i = 1, dim_lengths(2)
144  limiter_grid_construct%zgrid(i) = (i - 1)*dz + z0
145  END DO
146 
147  CALL profiler_set_stop_time('limiter_grid_construct', start_time)
148 
149  END FUNCTION
150 
151 !*******************************************************************************
152 ! DESTRUCTION SUBROUTINES
153 !*******************************************************************************
154 !-------------------------------------------------------------------------------
160 !-------------------------------------------------------------------------------
161  SUBROUTINE limiter_grid_destruct(this)
162 
163 ! Declare Arguments
164  TYPE (limiter_grid_class), POINTER :: this
165 
166 ! Start of executable code
167  IF (ASSOCIATED(this%phi)) THEN
168  DEALLOCATE(this%phi)
169  this%phi => null()
170  END IF
171 
172  IF (ASSOCIATED(this%grid)) THEN
173  DEALLOCATE(this%grid)
174  this%grid => null()
175  END IF
176 
177  IF (ASSOCIATED(this%rgrid)) THEN
178  DEALLOCATE(this%rgrid)
179  this%rgrid => null()
180  END IF
181 
182  IF (ASSOCIATED(this%zgrid)) THEN
183  DEALLOCATE(this%zgrid)
184  this%zgrid => null()
185  END IF
186 
187  END SUBROUTINE
188 
189 !*******************************************************************************
190 ! GETTER SUBROUTINES
191 !*******************************************************************************
192 !-------------------------------------------------------------------------------
202 !-------------------------------------------------------------------------------
203  FUNCTION limiter_grid_get_max_fval(this, num_theta, phi_index, &
204  & r, z, rphiz_at_max)
206 
207  IMPLICIT NONE
208 
209 ! Declare Arguments
210  REAL (rprec) :: limiter_grid_get_max_fval
211  class(limiter_grid_class), INTENT(in) :: this
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
217 
218 ! local variables
219  TYPE (bivariate_type), POINTER :: bivariate_object
220  INTEGER :: index
221  REAL (rprec), DIMENSION(:), ALLOCATABLE :: fval
222  REAL (rprec) :: start_time
223 
224 ! Start of executable code
225  start_time = profiler_get_start_time()
226 
227  limiter_grid_get_max_fval = -1.0e10
228  rphiz_at_max = 0.0
229 
230  ALLOCATE(fval(num_theta))
231  bivariate_object => bivariate_construct(1, num_theta)
232 
233  CALL bivariate_set_grids(bivariate_object, r, z, this%rgrid, &
234  & this%zgrid)
235  CALL bivariate_get_4pt(bivariate_object, &
236  & this%grid(:,:,phi_index), fval)
237 
238  index = maxloc(fval, 1)
239  IF (fval(index) .gt. limiter_grid_get_max_fval) THEN
240  limiter_grid_get_max_fval = fval(index)
241  rphiz_at_max = (/ r(index), this%phi(phi_index), z(index) /)
242  END IF
243 
244  CALL bivariate_destruct(bivariate_object)
245  DEALLOCATE(fval)
246 
247  CALL profiler_set_stop_time('limiter_grid_get_max_fval', &
248  & start_time)
249 
250  END FUNCTION
251 
252 !-------------------------------------------------------------------------------
259 !-------------------------------------------------------------------------------
260  FUNCTION limiter_grid_get_type(this)
262 
263  IMPLICIT NONE
264 
265 ! Declare Arguments
266  CHARACTER (len=data_name_length) :: limiter_grid_get_type
267  class(limiter_grid_class), INTENT(in) :: this
268 
269 ! local variables
270  REAL (rprec) :: start_time
271 
272 ! Start of executable code
273  start_time = profiler_get_start_time()
274 
276  & trim(this%limiter_class%get_type()) // 'grid'
277 
278  CALL profiler_set_stop_time('limiter_grid_get_type', &
279  & start_time)
280 
281  END FUNCTION
282 
283  END MODULE
limiter_grid::limiter_grid_get_max_fval
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.
Definition: limiter_grid.f:205
profiler
Defines functions for measuring an tabulating performance of function and subroutine calls....
Definition: profiler.f:13
limiter_grid::limiter_grid_get_type
character(len=data_name_length) function limiter_grid_get_type(this)
Gets a discription of the limiter grid type.
Definition: limiter_grid.f:261
limiter_grid::nc_dz
character(len= *), parameter nc_dz
NETCDF z grid spacing.
Definition: limiter_grid.f:31
limiter::limiter_class
Base class representing a limiter signal.
Definition: limiter.f:35
v3_utilities::assert_eq
Definition: v3_utilities.f:62
bivariate::bivariate_construct
type(bivariate_type) function, pointer bivariate_construct(ns, nu)
Construct a bivariate_type object.
Definition: bivariate.f:76
bivariate::bivariate_type
An object containing persistent data for the bivariate interpolation.
Definition: bivariate.f:27
limiter_grid::nc_r0
character(len= *), parameter nc_r0
NETCDF r grid start.
Definition: limiter_grid.f:25
bivariate::bivariate_destruct
subroutine bivariate_destruct(this)
Deconstruct a bivariate_type object.
Definition: bivariate.f:118
mpi_inc
Umbrella module avoid multiple inlcudes of the mpif.h header.
Definition: mpi_inc.f:11
bivariate::bivariate_set_grids
Interface for the setting of bivariate_type types either using bivariate_set_grids_1d or bivariate_se...
Definition: bivariate.f:57
limiter_grid::nc_phi_angles
character(len= *), parameter nc_phi_angles
NETCDF grid phi angles.
Definition: limiter_grid.f:33
profiler::profiler_get_start_time
real(rprec) function profiler_get_start_time()
Gets the start time of profiled function.
Definition: profiler.f:194
limiter_grid::nc_z0
character(len= *), parameter nc_z0
NETCDF z grid start.
Definition: limiter_grid.f:29
limiter_grid::limiter_grid_class
Base class representing a limiter signal.
Definition: limiter_grid.f:47
limiter_grid
Defines the base class of the type limiter_grid_class.
Definition: limiter_grid.f:13
limiter_grid::limiter_grid_destruct
subroutine limiter_grid_destruct(this)
Deconstruct a limiter_grid_class object.
Definition: limiter_grid.f:162
limiter_grid::nc_dr
character(len= *), parameter nc_dr
NETCDF r grid spacing.
Definition: limiter_grid.f:27
data_parameters
This modules contains parameters used by equilibrium models.
Definition: data_parameters.f:10
bivariate::bivariate_get_4pt
subroutine bivariate_get_4pt(this, resp_rz, resp_su)
Interpolate points on to responce function grid.
Definition: bivariate.f:391
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
limiter
Defines the base class of the type limiter_class.
Definition: limiter.f:15
bivariate
This modules contains routines for interpolating points inside a grid. This was originally written by...
Definition: bivariate.f:12
limiter_grid::nc_iso_grids
character(len= *), parameter nc_iso_grids
NETCDF grid iso surfaces.
Definition: limiter_grid.f:35
limiter_grid::limiter_grid_construct
class(limiter_grid_class) function, pointer limiter_grid_construct(lgrid_file, on_edge)
Construct a limiter_grid_class.
Definition: limiter_grid.f:89