Neko  0.8.1
A portable framework for high-order spectral element flow simulations
dong_outflow.f90
Go to the documentation of this file.
1 ! Copyright (c) 2022, 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 !
35  use neko_config
36  use dirichlet
37  use device
38  use num_types
39  use bc
40  use field
41  use dofmap
42  use coefs
43  use utils
46  use, intrinsic :: iso_c_binding, only : c_ptr, c_sizeof
47  implicit none
48  private
49 
55  type, public, extends(dirichlet_t) :: dong_outflow_t
56  type(field_t), pointer :: u
57  type(field_t), pointer :: v
58  type(field_t), pointer :: w
59  real(kind=rp) :: delta
60  real(kind=rp) :: uinf
61  type(c_ptr) :: normal_x_d
62  type(c_ptr) :: normal_y_d
63  type(c_ptr) :: normal_z_d
64  contains
65  procedure, pass(this) :: apply_scalar => dong_outflow_apply_scalar
66  procedure, pass(this) :: apply_vector => dong_outflow_apply_vector
67  procedure, pass(this) :: apply_scalar_dev => dong_outflow_apply_scalar_dev
68  procedure, pass(this) :: apply_vector_dev => dong_outflow_apply_vector_dev
69  procedure, pass(this) :: set_vars => dong_outflow_set_vars
70  end type dong_outflow_t
71 
72 contains
73  subroutine dong_outflow_set_vars(this, uinf, delta)
74  class(dong_outflow_t), intent(inout) :: this
75  real(kind=rp), intent(in) :: uinf
76  real(kind=rp), optional, intent(in) :: delta
77  real(kind=rp), allocatable :: temp_x(:)
78  real(kind=rp), allocatable :: temp_y(:)
79  real(kind=rp), allocatable :: temp_z(:)
80  real(c_rp) :: dummy
81  integer :: i, m, k, facet, idx(4)
82  real(kind=rp) :: normal_xyz(3)
83 
84 
85  if (present(delta)) then
86  this%delta = delta
87  else
88  this%delta = 0.01_rp
89  end if
90  this%uinf = uinf
91  this%u => neko_field_registry%get_field("u")
92  this%v => neko_field_registry%get_field("v")
93  this%w => neko_field_registry%get_field("w")
94  if ((neko_bcknd_device .eq. 1) .and. (this%msk(0) .gt. 0)) then
95  call device_alloc(this%normal_x_d,c_sizeof(dummy)*this%msk(0))
96  call device_alloc(this%normal_y_d,c_sizeof(dummy)*this%msk(0))
97  call device_alloc(this%normal_z_d,c_sizeof(dummy)*this%msk(0))
98  m = this%msk(0)
99  allocate(temp_x(m))
100  allocate(temp_y(m))
101  allocate(temp_z(m))
102  do i = 1, m
103  k = this%msk(i)
104  facet = this%facet(i)
105  idx = nonlinear_index(k,this%Xh%lx, this%Xh%lx,this%Xh%lx)
106  normal_xyz = &
107  this%coef%get_normal(idx(1), idx(2), idx(3), idx(4),facet)
108  temp_x(i) = normal_xyz(1)
109  temp_y(i) = normal_xyz(2)
110  temp_z(i) = normal_xyz(3)
111  end do
112  call device_memcpy(temp_x, this%normal_x_d, m, &
113  host_to_device, sync=.false.)
114  call device_memcpy(temp_y, this%normal_y_d, m, &
115  host_to_device, sync=.false.)
116  call device_memcpy(temp_z, this%normal_z_d, m, &
117  host_to_device, sync=.true.)
118  deallocate( temp_x, temp_y, temp_z)
119  end if
120  end subroutine dong_outflow_set_vars
121 
124  subroutine dong_outflow_apply_scalar(this, x, n, t, tstep)
125  class(dong_outflow_t), intent(inout) :: this
126  integer, intent(in) :: n
127  real(kind=rp), intent(inout), dimension(n) :: x
128  real(kind=rp), intent(in), optional :: t
129  integer, intent(in), optional :: tstep
130  integer :: i, m, k, facet, idx(4)
131  real(kind=rp) :: vn, s0, ux, uy, uz, normal_xyz(3)
132 
133  m = this%msk(0)
134  do i = 1, m
135  k = this%msk(i)
136  facet = this%facet(i)
137  ux = this%u%x(k,1,1,1)
138  uy = this%v%x(k,1,1,1)
139  uz = this%w%x(k,1,1,1)
140  idx = nonlinear_index(k,this%Xh%lx, this%Xh%lx,this%Xh%lx)
141  normal_xyz = this%coef%get_normal(idx(1), idx(2), idx(3), idx(4),facet)
142  vn = ux*normal_xyz(1) + uy*normal_xyz(2) + uz*normal_xyz(3)
143  s0 = 0.5_rp*(1.0_rp - tanh(vn / (this%uinf * this%delta)))
144 
145  x(k)=-0.5*(ux*ux+uy*uy+uz*uz)*s0
146  end do
147  end subroutine dong_outflow_apply_scalar
148 
151  subroutine dong_outflow_apply_vector(this, x, y, z, n, t, tstep)
152  class(dong_outflow_t), intent(inout) :: this
153  integer, intent(in) :: n
154  real(kind=rp), intent(inout), dimension(n) :: x
155  real(kind=rp), intent(inout), dimension(n) :: y
156  real(kind=rp), intent(inout), dimension(n) :: z
157  real(kind=rp), intent(in), optional :: t
158  integer, intent(in), optional :: tstep
159 
160  end subroutine dong_outflow_apply_vector
161 
164  subroutine dong_outflow_apply_scalar_dev(this, x_d, t, tstep)
165  class(dong_outflow_t), intent(inout), target :: this
166  type(c_ptr) :: x_d
167  real(kind=rp), intent(in), optional :: t
168  integer, intent(in), optional :: tstep
169 
170  call device_dong_outflow_apply_scalar(this%msk_d,x_d, this%normal_x_d, &
171  this%normal_y_d, this%normal_z_d,&
172  this%u%x_d, this%v%x_d, this%w%x_d,&
173  this%uinf, this%delta,&
174  this%msk(0))
175 
176  end subroutine dong_outflow_apply_scalar_dev
177 
180  subroutine dong_outflow_apply_vector_dev(this, x_d, y_d, z_d, t, tstep)
181  class(dong_outflow_t), intent(inout), target :: this
182  type(c_ptr) :: x_d
183  type(c_ptr) :: y_d
184  type(c_ptr) :: z_d
185  real(kind=rp), intent(in), optional :: t
186  integer, intent(in), optional :: tstep
187 
188  !call device_dong_outflow_apply_vector(this%msk_d, x_d, y_d, z_d, &
189  ! this%g, size(this%msk))
190 
191  end subroutine dong_outflow_apply_vector_dev
192 
193 end module dong_outflow
__device__ void nonlinear_index(const int idx, const int lx, int *index)
Copy data between host and device (or device and device)
Definition: device.F90:51
Defines a boundary condition.
Definition: bc.f90:34
Coefficients.
Definition: coef.f90:34
subroutine, public device_dong_outflow_apply_scalar(msk, x, normal_x, normal_y, normal_z, u, v, w, uinf, delta, m)
Device abstraction, common interface for various accelerators.
Definition: device.F90:34
integer, parameter, public host_to_device
Definition: device.F90:47
subroutine, public device_alloc(x_d, s)
Allocate memory on the device.
Definition: device.F90:151
Defines a dirichlet boundary condition.
Definition: dirichlet.f90:34
Defines a mapping of the degrees of freedom.
Definition: dofmap.f90:35
Defines a dong outflow condition.
subroutine dong_outflow_apply_vector(this, x, y, z, n, t, tstep)
Boundary condition apply for a generic Dirichlet condition to vectors x, y and z.
subroutine dong_outflow_apply_scalar(this, x, n, t, tstep)
Boundary condition apply for a generic Dirichlet condition to a vector x.
subroutine dong_outflow_apply_vector_dev(this, x_d, y_d, z_d, t, tstep)
Boundary condition apply for a generic Dirichlet condition to vectors x, y and z (device version)
subroutine dong_outflow_apply_scalar_dev(this, x_d, t, tstep)
Boundary condition apply for a generic Dirichlet condition to a vector x (device version)
subroutine dong_outflow_set_vars(this, uinf, delta)
Defines a registry for storing solution fields.
type(field_registry_t), target, public neko_field_registry
Global field registry.
Defines a field.
Definition: field.f90:34
Build configurations.
Definition: neko_config.f90:34
integer, parameter neko_bcknd_device
Definition: neko_config.f90:44
integer, parameter, public rp
Global precision used in computations.
Definition: num_types.f90:12
Utilities.
Definition: utils.f90:35
Generic Dirichlet boundary condition on .
Definition: dirichlet.f90:44
Dong outflow condition Follows "A Convective-like Energy-Stable Open Boundary Condition for Simulati...