43  use, 
intrinsic :: iso_c_binding
 
   59     real(kind=
rp), 
allocatable :: xh_to_yh(:,:), xh_to_yht(:,:)
 
   61     real(kind=
rp), 
allocatable :: yh_to_xh(:,:), yh_to_xht(:,:)
 
   63     type(c_ptr) :: xh_yh_d = c_null_ptr
 
   65     type(c_ptr) :: xh_yht_d = c_null_ptr
 
   67     type(c_ptr) :: yh_xh_d = c_null_ptr
 
   69     type(c_ptr) :: yh_xht_d = c_null_ptr
 
 
   90    type(
space_t), 
intent(inout), 
target :: Xh
 
   91    type(
space_t), 
intent(inout), 
target :: Yh
 
   92    integer :: deg_derivate
 
   96    allocate(this%Xh_to_Yh(yh%lx,xh%lx))
 
   97    allocate(this%Xh_to_YhT(xh%lx,yh%lx))
 
   98    allocate(this%Yh_to_Xh(xh%lx,yh%lx))
 
   99    allocate(this%Yh_to_XhT(yh%lx,xh%lx))
 
  101    if (xh%t .eq. 
gll .and. yh%t .eq. 
gll) 
then 
  102    else if ((xh%t .eq. 
gl .and. yh%t .eq. 
gll) .or. &
 
  103         (yh%t .eq. 
gl .and. xh%t .eq. 
gll)) 
then 
  108    call setup_intp(this%Xh_to_Yh, this%Xh_to_YhT, &
 
  109         yh%zg, xh%zg, yh%lx, xh%lx, deg_derivate)
 
  110    call setup_intp(this%Yh_to_Xh, this%Yh_to_XhT, &
 
  111         xh%zg, yh%zg, xh%lx, yh%lx, deg_derivate)
 
  116       call device_map(this%Xh_to_Yh, this%Xh_Yh_d, yh%lx*xh%lx)
 
  117       call device_map(this%Xh_to_YhT, this%Xh_YhT_d, yh%lx*xh%lx)
 
  118       call device_map(this%Yh_to_Xh, this%Yh_Xh_d, yh%lx*xh%lx)
 
  119       call device_map(this%Yh_to_XhT, this%Yh_XhT_d, yh%lx*xh%lx)
 
  120       call device_memcpy(this%Xh_to_Yh, this%Xh_Yh_d, yh%lx*xh%lx, &
 
  122       call device_memcpy(this%Xh_to_YhT, this%Xh_YhT_d, yh%lx*xh%lx, &
 
  124       call device_memcpy(this%Yh_to_Xh, this%Yh_Xh_d, yh%lx*xh%lx, &
 
  126       call device_memcpy(this%Yh_to_XhT, this%Yh_XhT_d, yh%lx*xh%lx, &
 
 
  135    if (
allocated(this%Xh_to_Yh)) 
then 
  136       deallocate(this%Xh_to_Yh)
 
  138    if (
allocated(this%Xh_to_YhT)) 
then 
  139       deallocate(this%Xh_to_YhT)
 
  141    if (
allocated(this%Yh_to_Xh)) 
then 
  142       deallocate(this%Yh_to_Xh)
 
  144    if (
allocated(this%Yh_to_XhT)) 
then 
  145       deallocate(this%Yh_to_XhT)
 
  147    if (c_associated(this%Yh_Xh_d)) 
then 
  150    if (c_associated(this%Yh_XhT_d)) 
then 
  153    if (c_associated(this%Xh_Yh_d)) 
then 
  156    if (c_associated(this%Xh_YhT_d)) 
then 
 
  171    real(kind=
rp), 
intent(in) :: x(this%Xh%lx, this%Xh%lx, this%Xh%lx, nel)
 
  172    real(kind=
rp), 
intent(inout) :: y(this%Yh%lx, this%Yh%lx, this%Yh%lx, nel)
 
  173    if (to_space .eq. this%Yh) 
then 
  174       call tnsr3d(y, this%Yh%lx, x, &
 
  175                   this%Xh%lx,this%Yh_to_XhT, &
 
  176                   this%Yh_to_Xh, this%Yh_to_Xh, nel)
 
  177    else if (to_space .eq. this%Xh) 
then 
  178       call tnsr3d(y, this%Xh%lx, x, &
 
  179                   this%Yh%lx,this%Yh_to_Xh, &
 
  180                   this%Yh_to_XhT, this%Yh_to_XhT, nel)
 
 
  197    real(kind=
rp), 
intent(inout) :: x(this%Xh%lx, this%Xh%lx, this%Xh%lx, nel)
 
  198    real(kind=
rp), 
intent(inout) :: y(this%Yh%lx, this%Yh%lx, this%Yh%lx, nel)
 
  199    if (to_space .eq. this%Yh) 
then 
  201                   this%Xh%lx,this%Yh_to_XhT, &
 
  202                   this%Yh_to_Xh, this%Yh_to_Xh, nel)
 
  203    else if (to_space .eq. this%Xh) 
then 
  205                   this%Yh%lx,this%Yh_to_Xh, &
 
  206                   this%Yh_to_XhT, this%Yh_to_XhT, nel)
 
 
Map a Fortran array to a device (allocate and associate)
 
Copy data between host and device (or device and device)
 
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 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 interpolate between different spaces.
 
subroutine interpolator_map_host(this, y, x, nel, to_space)
Interpolates an array to one of Xh or Yh on host.
 
subroutine interpolator_map(this, y, x, nel, to_space)
Interpolates an array to one of Xh or Yh.
 
subroutine interpolator_init(this, xh, yh)
Constructor to initialize with two different spaces.
 
subroutine interpolator_free(this)
 
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_cpu(v, nv, u, nu, a, bt, ct, nelv)
 
subroutine, public tnsr3d(v, nv, u, nu, a, bt, ct, nelv)
Tensor product  performed on nelv elements.
 
Interpolation between two space::space_t.
 
The function space for the SEM solution fields.