48 use,
intrinsic :: iso_c_binding
63 real(kind=
rp),
allocatable :: weights_r(:,:)
64 real(kind=
rp),
allocatable :: weights_s(:,:)
65 real(kind=
rp),
allocatable :: weights_t(:,:)
66 type(c_ptr) :: weights_r_d = c_null_ptr
67 type(c_ptr) :: weights_s_d = c_null_ptr
68 type(c_ptr) :: weights_t_d = c_null_ptr
87 type(
space_t),
intent(in),
target :: Xh
88 integer,
intent(in) :: n_points
89 real(kind=
rp) :: r(n_points), s(n_points), t(n_points)
90 integer :: size_weights
92 if ((xh%t .eq.
gl) .or. (xh%t .eq.
gll))
then
98 this%n_points = n_points
99 allocate(this%weights_r(xh%lx,n_points))
100 allocate(this%weights_s(xh%ly,n_points))
101 allocate(this%weights_t(xh%lz,n_points))
102 call this%compute_weights(r, s, t)
103 size_weights = xh%lx * n_points
106 call device_map(this%weights_r, this%weights_r_d, size_weights)
107 call device_map(this%weights_s, this%weights_s_d, size_weights)
108 call device_map(this%weights_t, this%weights_t_d, size_weights)
123 if (
associated(this%Xh)) this%Xh => null()
125 if(
allocated(this%weights_r))
deallocate(this%weights_r)
126 if(
allocated(this%weights_s))
deallocate(this%weights_s)
127 if(
allocated(this%weights_t))
deallocate(this%weights_t)
128 if (c_associated(this%weights_r_d))
then
131 if (c_associated(this%weights_s_d))
then
134 if (c_associated(this%weights_t_d))
then
151 real(kind=
rp),
intent(in) :: r(:), s(:), t(:)
158 call fd_weights_full(r(i), this%Xh%zg(:,1), lx-1, 0, this%weights_r(:,i))
159 call fd_weights_full(s(i), this%Xh%zg(:,2), lx-1, 0, this%weights_s(:,i))
160 call fd_weights_full(t(i), this%Xh%zg(:,3), lx-1, 0, this%weights_t(:,i))
179 integer,
intent(in) :: el_list(this%n_points)
180 integer,
intent(in) :: nel
181 real(kind=
rp),
intent(inout) :: interp_values(this%n_points)
182 real(kind=
rp),
intent(inout) ::
field(this%Xh%lxyz, nel)
186 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.