61     real(kind=
rp), 
allocatable :: weights_r(:,:)
 
   62     real(kind=
rp), 
allocatable :: weights_s(:,:)
 
   63     real(kind=
rp), 
allocatable :: weights_t(:,:)
 
   64     type(c_ptr) :: weights_r_d = c_null_ptr
 
   65     type(c_ptr) :: weights_s_d = c_null_ptr
 
   66     type(c_ptr) :: weights_t_d = c_null_ptr
 
 
   85    type(
space_t), 
intent(in), 
target :: Xh
 
   86    integer, 
intent(in) :: n_points
 
   87    real(kind=
rp) :: r(n_points), s(n_points), t(n_points)
 
   88    integer :: size_weights
 
   90    if ((xh%t .eq. 
gl) .or. (xh%t .eq. 
gll)) 
then 
   96    this%n_points = n_points
 
   97    allocate(this%weights_r(xh%lx,n_points))
 
   98    allocate(this%weights_s(xh%ly,n_points))
 
   99    allocate(this%weights_t(xh%lz,n_points))
 
  100    call this%compute_weights(r, s, t)
 
  101    size_weights = xh%lx * n_points
 
  104       call device_map(this%weights_r, this%weights_r_d, size_weights)
 
  105       call device_map(this%weights_s, this%weights_s_d, size_weights)
 
  106       call device_map(this%weights_t, this%weights_t_d, size_weights)
 
 
  121    if (
associated(this%Xh)) this%Xh => null()
 
  123    if(
allocated(this%weights_r)) 
deallocate(this%weights_r)
 
  124    if(
allocated(this%weights_s)) 
deallocate(this%weights_s)
 
  125    if(
allocated(this%weights_t)) 
deallocate(this%weights_t)
 
  126    if (c_associated(this%weights_r_d)) 
then 
  129    if (c_associated(this%weights_s_d)) 
then 
  132    if (c_associated(this%weights_t_d)) 
then 
 
  149    real(kind=
rp), 
intent(in) :: r(:), s(:), t(:)
 
  156       call fd_weights_full(r(i), this%Xh%zg(:,1), lx-1, 0, this%weights_r(:,i))
 
  157       call fd_weights_full(s(i), this%Xh%zg(:,2), lx-1, 0, this%weights_s(:,i))
 
  158       call fd_weights_full(t(i), this%Xh%zg(:,3), lx-1, 0, this%weights_t(:,i))
 
 
  177    integer, 
intent(in) :: el_list(this%n_points)
 
  178    integer, 
intent(in) :: nel
 
  179    real(kind=
rp), 
intent(inout) :: interp_values(this%n_points)
 
  180    real(kind=
rp), 
intent(inout) :: 
field(this%Xh%lxyz, nel)
 
  184         this%weights_r, this%weights_s, this%weights_t, el_list, this%n_points)
 
 
Map a Fortran array to a device (allocate and associate)
 
Copy data between host and device (or device and device)
 
subroutine, public device_rzero(a_d, n)
Zero a real vector.
 
Device abstraction, common interface for various accelerators.
 
integer, parameter, public host_to_device
 
subroutine, public device_free(x_d)
Deallocate memory on the device.
 
Fast diagonalization methods from NEKTON.
 
subroutine, public fd_weights_full(xi, x, n, m, c)
Compute finite-difference stencil weights for evaluating derivatives up to order  at a point.
 
subroutine, public setup_intp(jh, jht, z_to, z_from, n_to, n_from, derivative)
Compute interpolation weights for points z_to using values at points z_from.
 
Routines to obtain interpolated values on a set of points with known rst coordinates in elements loca...
 
subroutine local_interpolator_compute_weights(this, r, s, t)
Computes interpolation weights  for a list of points.
 
subroutine local_interpolator_init(this, xh, r, s, t, n_points)
Initialization of point interpolation.
 
subroutine local_interpolator_evaluate(this, interp_values, el_list, field, nel)
Interpolates a list of fields based on a set of element ids.
 
subroutine local_interpolator_free(this)
Free pointers.
 
integer, parameter neko_bcknd_device
 
integer, parameter, public rp
Global precision used in computations.
 
Defines a function space.
 
integer, parameter, public gll
 
integer, parameter, public gl
 
subroutine, public tnsr3d_el_list(v, nv, u, nu, a, bt, ct, el_list, n_pt)
Tensor product  performed on a subset of the elements.
 
field_list_t, To be able to group fields together
 
Interpolation on a set of points with known rst coordinates in elements local to this process....
 
A point in  with coordinates .
 
The function space for the SEM solution fields.