Neko  0.8.1
A portable framework for high-order spectral element flow simulations
advection.f90
Go to the documentation of this file.
1 ! Copyright (c) 2021-2024, The Neko Authors
2 ! All rights reserved.
3 !
4 ! Redistribution and use in source and binary forms, with or without
5 ! modification, are permitted provided that the following conditions
6 ! are met:
7 !
8 ! * Redistributions of source code must retain the above copyright
9 ! notice, this list of conditions and the following disclaimer.
10 !
11 ! * Redistributions in binary form must reproduce the above
12 ! copyright notice, this list of conditions and the following
13 ! disclaimer in the documentation and/or other materials provided
14 ! with the distribution.
15 !
16 ! * Neither the name of the authors nor the names of its
17 ! contributors may be used to endorse or promote products derived
18 ! from this software without specific prior written permission.
19 !
20 ! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
21 ! "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
22 ! LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
23 ! FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
24 ! COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
25 ! INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
26 ! BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
27 ! LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
28 ! CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
29 ! LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
30 ! ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
31 ! POSSIBILITY OF SUCH DAMAGE.
32 !
34 module advection
35  use num_types, only : rp
36  use math
37  use utils
38  use space, only : space_t, gl
39  use field, only : field_t
40  use coefs, only : coef_t
41  use device_math
42  use neko_config
43  use operators
44  use interpolation
45  use device_math
47  use, intrinsic :: iso_c_binding, only : c_ptr, c_null_ptr, &
48  c_associated
49  implicit none
50  private
51 
53  type, public, abstract :: advection_t
54  contains
55  procedure(compute_adv), pass(this), deferred :: compute
56  procedure(compute_scalar_adv), pass(this), deferred :: compute_scalar
57  procedure(advection_free), pass(this), deferred :: free
58  end type advection_t
59 
61  type, public, extends(advection_t) :: adv_no_dealias_t
62  real(kind=rp), allocatable :: temp(:)
63  type(c_ptr) :: temp_d = c_null_ptr
64  contains
66  procedure, pass(this) :: init => init_no_dealias
68  procedure, pass(this) :: free => free_no_dealias
71  procedure, pass(this) :: compute => compute_advection_no_dealias
74  procedure, pass(this) :: compute_scalar => &
76  end type adv_no_dealias_t
77 
79  type, public, extends(advection_t) :: adv_dealias_t
81  type(coef_t) :: coef_gl
83  type(coef_t), pointer :: coef_gll
85  type(interpolator_t) :: gll_to_gl
87  type(space_t) :: xh_gl
89  type(space_t), pointer :: xh_gll
90  real(kind=rp), allocatable :: temp(:), tbf(:)
92  real(kind=rp), allocatable :: tx(:), ty(:), tz(:)
93  real(kind=rp), allocatable :: vr(:), vs(:), vt(:)
95  type(c_ptr) :: temp_d = c_null_ptr
97  type(c_ptr) :: tbf_d = c_null_ptr
99  type(c_ptr) :: tx_d = c_null_ptr
101  type(c_ptr) :: ty_d = c_null_ptr
103  type(c_ptr) :: tz_d = c_null_ptr
105  type(c_ptr) :: vr_d = c_null_ptr
107  type(c_ptr) :: vs_d = c_null_ptr
109  type(c_ptr) :: vt_d = c_null_ptr
110 
111  contains
114  procedure, pass(this) :: compute => compute_advection_dealias
117  procedure, pass(this) :: compute_scalar => compute_scalar_advection_dealias
119  procedure, pass(this) :: init => init_dealias
121  procedure, pass(this) :: free => free_dealias
122  end type adv_dealias_t
123 
124  abstract interface
125 
136  subroutine compute_adv(this, vx, vy, vz, fx, fy, fz, Xh, coef, n)
137  import :: advection_t
138  import :: coef_t
139  import :: space_t
140  import :: field_t
141  import :: rp
142  class(advection_t), intent(inout) :: this
143  type(space_t), intent(inout) :: Xh
144  type(coef_t), intent(inout) :: coef
145  type(field_t), intent(inout) :: vx, vy, vz
146  integer, intent(in) :: n
147  real(kind=rp), intent(inout), dimension(n) :: fx, fy, fz
148  end subroutine compute_adv
149  end interface
150 
151  abstract interface
152 
162  subroutine compute_scalar_adv(this, vx, vy, vz, s, fs, Xh, coef, n)
163  import :: advection_t
164  import :: coef_t
165  import :: space_t
166  import :: field_t
167  import :: rp
168  class(advection_t), intent(inout) :: this
169  type(field_t), intent(inout) :: vx, vy, vz
170  type(field_t), intent(inout) :: s
171  real(kind=rp), intent(inout), dimension(n) :: fs
172  type(space_t), intent(inout) :: xh
173  type(coef_t), intent(inout) :: coef
174  integer, intent(in) :: n
175  end subroutine compute_scalar_adv
176  end interface
177 
178  abstract interface
179 
180  subroutine advection_free(this)
181  import :: advection_t
182  class(advection_t), intent(inout) :: this
183  end subroutine advection_free
184  end interface
185 
186 contains
187 
190  subroutine init_no_dealias(this, coef)
191  class(adv_no_dealias_t), intent(inout) :: this
192  type(coef_t), intent(in) :: coef
193 
194  allocate(this%temp(coef%dof%size()))
195 
196  if (neko_bcknd_device .eq. 1) then
197  call device_map(this%temp, this%temp_d, coef%dof%size())
198  end if
199 
200  end subroutine init_no_dealias
201 
203  subroutine free_no_dealias(this)
204  class(adv_no_dealias_t), intent(inout) :: this
205 
206  if (allocated(this%temp)) then
207  deallocate(this%temp)
208  end if
209  if (c_associated(this%temp_d)) then
210  call device_free(this%temp_d)
211  end if
212  end subroutine free_no_dealias
213 
217  subroutine init_dealias(this, lxd, coef)
218  class(adv_dealias_t), target, intent(inout) :: this
219  integer, intent(in) :: lxd
220  type(coef_t), intent(inout), target :: coef
221  integer :: nel, n_GL, n
222 
223  call this%Xh_GL%init(gl, lxd, lxd, lxd)
224  this%Xh_GLL => coef%Xh
225  this%coef_GLL => coef
226  call this%GLL_to_GL%init(this%Xh_GL, this%Xh_GLL)
227 
228  call this%coef_GL%init(this%Xh_GL, coef%msh)
229 
230  nel = coef%msh%nelv
231  n_gl = nel*this%Xh_GL%lxyz
232  n = nel*coef%Xh%lxyz
233  call this%GLL_to_GL%map(this%coef_GL%drdx, coef%drdx, nel, this%Xh_GL)
234  call this%GLL_to_GL%map(this%coef_GL%dsdx, coef%dsdx, nel, this%Xh_GL)
235  call this%GLL_to_GL%map(this%coef_GL%dtdx, coef%dtdx, nel, this%Xh_GL)
236  call this%GLL_to_GL%map(this%coef_GL%drdy, coef%drdy, nel, this%Xh_GL)
237  call this%GLL_to_GL%map(this%coef_GL%dsdy, coef%dsdy, nel, this%Xh_GL)
238  call this%GLL_to_GL%map(this%coef_GL%dtdy, coef%dtdy, nel, this%Xh_GL)
239  call this%GLL_to_GL%map(this%coef_GL%drdz, coef%drdz, nel, this%Xh_GL)
240  call this%GLL_to_GL%map(this%coef_GL%dsdz, coef%dsdz, nel, this%Xh_GL)
241  call this%GLL_to_GL%map(this%coef_GL%dtdz, coef%dtdz, nel, this%Xh_GL)
242  if ((neko_bcknd_hip .eq. 1) .or. (neko_bcknd_cuda .eq. 1) .or. &
243  (neko_bcknd_opencl .eq. 1) .or. (neko_bcknd_sx .eq. 1) .or. &
244  (neko_bcknd_xsmm .eq. 1)) then
245  allocate(this%temp(n_gl))
246  allocate(this%tbf(n_gl))
247  allocate(this%tx(n_gl))
248  allocate(this%ty(n_gl))
249  allocate(this%tz(n_gl))
250  allocate(this%vr(n_gl))
251  allocate(this%vs(n_gl))
252  allocate(this%vt(n_gl))
253  end if
254 
255  if (neko_bcknd_device .eq. 1) then
256  call device_map(this%temp, this%temp_d, n_gl)
257  call device_map(this%tbf, this%tbf_d, n_gl)
258  call device_map(this%tx, this%tx_d, n_gl)
259  call device_map(this%ty, this%ty_d, n_gl)
260  call device_map(this%tz, this%tz_d, n_gl)
261  call device_map(this%vr, this%vr_d, n_gl)
262  call device_map(this%vs, this%vs_d, n_gl)
263  call device_map(this%vt, this%vt_d, n_gl)
264  end if
265 
266  end subroutine init_dealias
267 
269  subroutine free_dealias(this)
270  class(adv_dealias_t), intent(inout) :: this
271  end subroutine free_dealias
272 
273 
285  subroutine compute_advection_dealias(this, vx, vy, vz, fx, fy, fz, Xh, coef, n)
286  class(adv_dealias_t), intent(inout) :: this
287  type(space_t), intent(inout) :: Xh
288  type(coef_t), intent(inout) :: coef
289  type(field_t), intent(inout) :: vx, vy, vz
290  integer, intent(in) :: n
291  real(kind=rp), intent(inout), dimension(n) :: fx, fy, fz
292  real(kind=rp), dimension(this%Xh_GL%lxyz) :: tx, ty, tz
293  real(kind=rp), dimension(this%Xh_GL%lxyz) :: tfx, tfy, tfz
294  real(kind=rp), dimension(this%Xh_GL%lxyz) :: vr, vs, vt
295  real(kind=rp), dimension(this%Xh_GLL%lxyz) :: tempx, tempy, tempz
296  type(c_ptr) :: fx_d, fy_d, fz_d
297  integer :: e, i, idx, nel, n_gl
298  nel = coef%msh%nelv
299  n_gl = nel * this%Xh_GL%lxyz
300  !This is extremely primitive and unoptimized on the device //Karp
301  associate(c_gl => this%coef_GL)
302  if (neko_bcknd_device .eq. 1) then
303  fx_d = device_get_ptr(fx)
304  fy_d = device_get_ptr(fy)
305  fz_d = device_get_ptr(fz)
306  call this%GLL_to_GL%map(this%tx, vx%x, nel, this%Xh_GL)
307  call this%GLL_to_GL%map(this%ty, vy%x, nel, this%Xh_GL)
308  call this%GLL_to_GL%map(this%tz, vz%x, nel, this%Xh_GL)
309 
310  call opgrad(this%vr, this%vs, this%vt, this%tx, c_gl)
311  call device_vdot3(this%tbf_d, this%vr_d, this%vs_d, this%vt_d, &
312  this%tx_d, this%ty_d, this%tz_d, n_gl)
313  call this%GLL_to_GL%map(this%temp, this%tbf, nel, this%Xh_GLL)
314  call device_sub2(fx_d, this%temp_d, n)
315 
316 
317  call opgrad(this%vr, this%vs, this%vt, this%ty, c_gl)
318  call device_vdot3(this%tbf_d, this%vr_d, this%vs_d, this%vt_d, &
319  this%tx_d, this%ty_d, this%tz_d, n_gl)
320  call this%GLL_to_GL%map(this%temp, this%tbf, nel, this%Xh_GLL)
321  call device_sub2(fy_d, this%temp_d, n)
322 
323  call opgrad(this%vr, this%vs, this%vt, this%tz, c_gl)
324  call device_vdot3(this%tbf_d, this%vr_d, this%vs_d, this%vt_d, &
325  this%tx_d, this%ty_d, this%tz_d, n_gl)
326  call this%GLL_to_GL%map(this%temp, this%tbf, nel, this%Xh_GLL)
327  call device_sub2(fz_d, this%temp_d, n)
328 
329  else if ((neko_bcknd_sx .eq. 1) .or. (neko_bcknd_xsmm .eq. 1)) then
330 
331  call this%GLL_to_GL%map(this%tx, vx%x, nel, this%Xh_GL)
332  call this%GLL_to_GL%map(this%ty, vy%x, nel, this%Xh_GL)
333  call this%GLL_to_GL%map(this%tz, vz%x, nel, this%Xh_GL)
334 
335  call opgrad(this%vr, this%vs, this%vt, this%tx, c_gl)
336  call vdot3(this%tbf, this%vr, this%vs, this%vt, &
337  this%tx, this%ty, this%tz, n_gl)
338  call this%GLL_to_GL%map(this%temp, this%tbf, nel, this%Xh_GLL)
339  call sub2(fx, this%temp, n)
340 
341 
342  call opgrad(this%vr, this%vs, this%vt, this%ty, c_gl)
343  call vdot3(this%tbf, this%vr, this%vs, this%vt, &
344  this%tx, this%ty, this%tz, n_gl)
345  call this%GLL_to_GL%map(this%temp, this%tbf, nel, this%Xh_GLL)
346  call sub2(fy, this%temp, n)
347 
348  call opgrad(this%vr, this%vs, this%vt, this%tz, c_gl)
349  call vdot3(this%tbf, this%vr, this%vs, this%vt, &
350  this%tx, this%ty, this%tz, n_gl)
351  call this%GLL_to_GL%map(this%temp, this%tbf, nel, this%Xh_GLL)
352  call sub2(fz, this%temp, n)
353 
354  else
355 
356  do e = 1, coef%msh%nelv
357  call this%GLL_to_GL%map(tx, vx%x(1,1,1,e), 1, this%Xh_GL)
358  call this%GLL_to_GL%map(ty, vy%x(1,1,1,e), 1, this%Xh_GL)
359  call this%GLL_to_GL%map(tz, vz%x(1,1,1,e), 1, this%Xh_GL)
360 
361  call opgrad(vr, vs, vt, tx, c_gl, e, e)
362  do i = 1, this%Xh_GL%lxyz
363  tfx(i) = tx(i)*vr(i) + ty(i)*vs(i) + tz(i)*vt(i)
364  end do
365 
366  call opgrad(vr, vs, vt, ty, c_gl, e, e)
367  do i = 1, this%Xh_GL%lxyz
368  tfy(i) = tx(i)*vr(i) + ty(i)*vs(i) + tz(i)*vt(i)
369  end do
370 
371  call opgrad(vr, vs, vt, tz, c_gl, e, e)
372  do i = 1, this%Xh_GL%lxyz
373  tfz(i) = tx(i)*vr(i) + ty(i)*vs(i) + tz(i)*vt(i)
374  end do
375 
376  call this%GLL_to_GL%map(tempx, tfx, 1, this%Xh_GLL)
377  call this%GLL_to_GL%map(tempy, tfy, 1, this%Xh_GLL)
378  call this%GLL_to_GL%map(tempz, tfz, 1, this%Xh_GLL)
379 
380  idx = (e-1)*this%Xh_GLL%lxyz+1
381  call sub2(fx(idx), tempx, this%Xh_GLL%lxyz)
382  call sub2(fy(idx), tempy, this%Xh_GLL%lxyz)
383  call sub2(fz(idx), tempz, this%Xh_GLL%lxyz)
384  end do
385  end if
386  end associate
387 
388  end subroutine compute_advection_dealias
389 
401  subroutine compute_advection_no_dealias(this, vx, vy, vz, fx, fy, fz, Xh, coef, n)
402  class(adv_no_dealias_t), intent(inout) :: this
403  type(space_t), intent(inout) :: Xh
404  type(coef_t), intent(inout) :: coef
405  type(field_t), intent(inout) :: vx, vy, vz
406  integer, intent(in) :: n
407  real(kind=rp), intent(inout), dimension(n) :: fx, fy, fz
408  type(c_ptr) :: fx_d, fy_d, fz_d
409 
410  if (neko_bcknd_device .eq. 1) then
411  fx_d = device_get_ptr(fx)
412  fy_d = device_get_ptr(fy)
413  fz_d = device_get_ptr(fz)
414 
415  call conv1(this%temp, vx%x, vx%x, vy%x, vz%x, xh, coef)
416  call device_subcol3 (fx_d, coef%B_d, this%temp_d, n)
417  call conv1(this%temp, vy%x, vx%x, vy%x, vz%x, xh, coef)
418  call device_subcol3 (fy_d, coef%B_d, this%temp_d, n)
419  if (coef%Xh%lz .eq. 1) then
420  call device_rzero (this%temp_d, n)
421  else
422  call conv1(this%temp, vz%x, vx%x, vy%x, vz%x, xh, coef)
423  call device_subcol3(fz_d, coef%B_d, this%temp_d, n)
424  end if
425  else
426  call conv1(this%temp, vx%x, vx%x, vy%x, vz%x, xh, coef)
427  call subcol3 (fx, coef%B, this%temp, n)
428  call conv1(this%temp, vy%x, vx%x, vy%x, vz%x, xh, coef)
429  call subcol3 (fy, coef%B, this%temp, n)
430  if (coef%Xh%lz .eq. 1) then
431  call rzero (this%temp, n)
432  else
433  call conv1(this%temp, vz%x, vx%x, vy%x, vz%x, xh, coef)
434  call subcol3(fz, coef%B, this%temp, n)
435  end if
436  end if
437 
438  end subroutine compute_advection_no_dealias
439 
451  subroutine compute_scalar_advection_no_dealias(this, vx, vy, vz, s, fs, Xh, &
452  coef, n)
453  class(adv_no_dealias_t), intent(inout) :: this
454  type(field_t), intent(inout) :: vx, vy, vz
455  type(field_t), intent(inout) :: s
456  integer, intent(in) :: n
457  real(kind=rp), intent(inout), dimension(n) :: fs
458  type(space_t), intent(inout) :: xh
459  type(coef_t), intent(inout) :: coef
460  type(c_ptr) :: fs_d
461 
462  if (neko_bcknd_device .eq. 1) then
463  fs_d = device_get_ptr(fs)
464 
465  call conv1(this%temp, s%x, vx%x, vy%x, vz%x, xh, coef)
466  call device_subcol3 (fs_d, coef%B_d, this%temp_d, n)
467  if (coef%Xh%lz .eq. 1) then
468  call device_rzero (this%temp_d, n)
469  end if
470  else
471  ! temp will hold vx*ds/dx + vy*ds/dy + vz*ds/sz
472  call conv1(this%temp, s%x, vx%x, vy%x, vz%x, xh, coef)
473 
474  ! fs = fs - B*temp
475  call subcol3 (fs, coef%B, this%temp, n)
476  if (coef%Xh%lz .eq. 1) then
477  call rzero (this%temp, n)
478  end if
479  end if
480 
482 
494  subroutine compute_scalar_advection_dealias(this, vx, vy, vz, s, fs, Xh, &
495  coef, n)
496  class(adv_dealias_t), intent(inout) :: this
497  type(field_t), intent(inout) :: vx, vy, vz
498  type(field_t), intent(inout) :: s
499  integer, intent(in) :: n
500  real(kind=rp), intent(inout), dimension(n) :: fs
501  type(space_t), intent(inout) :: xh
502  type(coef_t), intent(inout) :: coef
503  type(c_ptr) :: fs_d
504  real(kind=rp), dimension(this%Xh_GL%lxyz) :: vx_gl, vy_gl, vz_gl, s_gl
505  real(kind=rp), dimension(this%Xh_GL%lxyz) :: dsdx, dsdy, dsdz
506  real(kind=rp), dimension(this%Xh_GL%lxyz) :: f_gl
507  integer :: e, i, idx, nel, n_GL
508  real(kind=rp), dimension(this%Xh_GLL%lxyz) :: temp
509 
510  nel = coef%msh%nelv
511  n_gl = nel * this%Xh_GL%lxyz
512 
513  associate(c_gl => this%coef_GL)
514  if (neko_bcknd_device .eq. 1) then
515  fs_d = device_get_ptr(fs)
516 
517  ! Map advecting velocity onto the higher-order space
518  call this%GLL_to_GL%map(this%tx, vx%x, nel, this%Xh_GL)
519  call this%GLL_to_GL%map(this%ty, vy%x, nel, this%Xh_GL)
520  call this%GLL_to_GL%map(this%tz, vz%x, nel, this%Xh_GL)
521 
522  ! Map the scalar onto the high-order space
523  call this%GLL_to_GL%map(this%temp, s%x, nel, this%Xh_GL)
524 
525  ! Compute the scalar gradient in the high-order space
526  call opgrad(this%vr, this%vs, this%vt, this%temp, c_gl)
527 
528  ! Compute the convective term, i.e dot the velocity with the scalar grad
529  call device_vdot3(this%tbf_d, this%vr_d, this%vs_d, this%vt_d, &
530  this%tx_d, this%ty_d, this%tz_d, n_gl)
531 
532  ! Map back to the original space (we reuse this%temp)
533  call this%GLL_to_GL%map(this%temp, this%tbf, nel, this%Xh_GLL)
534 
535  ! Update the source term
536  call device_sub2(fs_d, this%temp_d, n)
537 
538  else if ((neko_bcknd_sx .eq. 1) .or. (neko_bcknd_xsmm .eq. 1)) then
539 
540  ! Map advecting velocity onto the higher-order space
541  call this%GLL_to_GL%map(this%tx, vx%x, nel, this%Xh_GL)
542  call this%GLL_to_GL%map(this%ty, vy%x, nel, this%Xh_GL)
543  call this%GLL_to_GL%map(this%tz, vz%x, nel, this%Xh_GL)
544 
545  ! Map the scalar onto the high-order space
546  call this%GLL_to_GL%map(this%temp, s%x, nel, this%Xh_GL)
547 
548  ! Compute the scalar gradient in the high-order space
549  call opgrad(this%vr, this%vs, this%vt, this%temp, c_gl)
550 
551  ! Compute the convective term, i.e dot the velocity with the scalar grad
552  call vdot3(this%tbf, this%vr, this%vs, this%vt, &
553  this%tx, this%ty, this%tz, n_gl)
554 
555  ! Map back to the original space (we reuse this%temp)
556  call this%GLL_to_GL%map(this%temp, this%tbf, nel, this%Xh_GLL)
557 
558  ! Update the source term
559  call sub2(fs, this%temp, n)
560 
561  else
562  do e = 1, coef%msh%nelv
563  ! Map advecting velocity onto the higher-order space
564  call this%GLL_to_GL%map(vx_gl, vx%x(1,1,1,e), 1, this%Xh_GL)
565  call this%GLL_to_GL%map(vy_gl, vy%x(1,1,1,e), 1, this%Xh_GL)
566  call this%GLL_to_GL%map(vz_gl, vz%x(1,1,1,e), 1, this%Xh_GL)
567 
568  ! Map scalar onto the higher-order space
569  call this%GLL_to_GL%map(s_gl, s%x(1,1,1,e), 1, this%Xh_GL)
570 
571  ! Gradient of s in the higher-order space
572  call opgrad(dsdx, dsdy, dsdz, s_gl, c_gl, e, e)
573 
574  ! vx * ds/dx + vy * ds/dy + vz * ds/dz for each point in the element
575  do i = 1, this%Xh_GL%lxyz
576  f_gl(i) = vx_gl(i)*dsdx(i) + vy_gl(i)*dsdy(i) + vz_gl(i)*dsdz(i)
577  end do
578 
579  ! Map back the contructed operator to the original space
580  call this%GLL_to_GL%map(temp, f_gl, 1, this%Xh_GLL)
581 
582  idx = (e-1)*this%Xh_GLL%lxyz + 1
583 
584  call sub2(fs(idx), temp, this%Xh_GLL%lxyz)
585  end do
586  end if
587  end associate
588 
589  end subroutine compute_scalar_advection_dealias
590 
591 end module advection
Add advection operator to the right-hand-side for a fluld.
Definition: advection.f90:136
Add advection operator to the right-hand-side for a scalar.
Definition: advection.f90:162
Return the device pointer for an associated Fortran array.
Definition: device.F90:81
Map a Fortran array to a device (allocate and associate)
Definition: device.F90:57
Subroutines to add advection terms to the RHS of a transport equation.
Definition: advection.f90:34
subroutine init_dealias(this, lxd, coef)
Constructor.
Definition: advection.f90:218
subroutine compute_advection_no_dealias(this, vx, vy, vz, fx, fy, fz, Xh, coef, n)
Add the advection term for the fluid, i.e. to the RHS.
Definition: advection.f90:402
subroutine compute_advection_dealias(this, vx, vy, vz, fx, fy, fz, Xh, coef, n)
Add the advection term for the fluid, i.e. , to the RHS.
Definition: advection.f90:286
subroutine init_no_dealias(this, coef)
Constructor.
Definition: advection.f90:191
subroutine compute_scalar_advection_dealias(this, vx, vy, vz, s, fs, Xh, coef, n)
Add the advection term for a scalar, i.e. , to the RHS.
Definition: advection.f90:496
subroutine free_no_dealias(this)
Destructor.
Definition: advection.f90:204
subroutine compute_scalar_advection_no_dealias(this, vx, vy, vz, s, fs, Xh, coef, n)
Add the advection term for a scalar, i.e. , to the RHS.
Definition: advection.f90:453
subroutine free_dealias(this)
Destructor.
Definition: advection.f90:270
Coefficients.
Definition: coef.f90:34
subroutine, public device_vdot3(dot_d, u1_d, u2_d, u3_d, v1_d, v2_d, v3_d, n)
subroutine, public device_sub2(a_d, b_d, n)
Device abstraction, common interface for various accelerators.
Definition: device.F90:34
subroutine, public device_free(x_d)
Deallocate memory on the device.
Definition: device.F90:172
Defines a field.
Definition: field.f90:34
Routines to interpolate between different spaces.
Definition: math.f90:60
subroutine, public vdot3(dot, u1, u2, u3, v1, v2, v3, n)
Compute a dot product (3-d version) assuming vector components etc.
Definition: math.f90:461
subroutine, public sub2(a, b, n)
Vector substraction .
Definition: math.f90:545
Build configurations.
Definition: neko_config.f90:34
integer, parameter neko_bcknd_sx
Definition: neko_config.f90:39
integer, parameter neko_bcknd_hip
Definition: neko_config.f90:42
integer, parameter neko_bcknd_device
Definition: neko_config.f90:44
integer, parameter neko_bcknd_opencl
Definition: neko_config.f90:43
integer, parameter neko_bcknd_cuda
Definition: neko_config.f90:41
integer, parameter neko_bcknd_xsmm
Definition: neko_config.f90:40
integer, parameter, public rp
Global precision used in computations.
Definition: num_types.f90:12
Operators.
Definition: operators.f90:34
subroutine, public opgrad(ux, uy, uz, u, coef, es, ee)
Compute the gradient of a scalar field.
Definition: operators.f90:100
Defines a function space.
Definition: space.f90:34
integer, parameter, public gl
Definition: space.f90:48
Utilities.
Definition: utils.f90:35
Type encapsulating advection routines with dealiasing.
Definition: advection.f90:79
Type encapsulating advection routines with no dealiasing applied.
Definition: advection.f90:61
Base abstract type for computing the advection operator.
Definition: advection.f90:53
Coefficients defined on a given (mesh, ) tuple. Arrays use indices (i,j,k,e): element e,...
Definition: coef.f90:54
Interpolation between two space::space_t.
The function space for the SEM solution fields.
Definition: space.f90:62