46 use,
intrinsic :: iso_c_binding, only : c_ptr, c_sizeof, c_null_ptr, &
48 use json_module,
only : json_file
64 real(kind=
rp) :: delta
66 type(c_ptr) :: normal_x_d = c_null_ptr
67 type(c_ptr) :: normal_y_d = c_null_ptr
68 type(c_ptr) :: normal_z_d = c_null_ptr
88 type(
coef_t),
target,
intent(in) :: coef
89 type(json_file),
intent(inout) :: json
91 call this%init_base(coef)
102 integer,
intent(in) :: n
103 real(kind=
rp),
intent(inout),
dimension(n) :: x
105 logical,
intent(in),
optional :: strong
106 integer :: i, m, k, facet, idx(4)
107 real(kind=
rp) :: vn, s0, ux, uy, uz, normal_xyz(3)
110 if (
present(strong))
then
121 facet = this%facet(i)
122 ux = this%u%x(k,1,1,1)
123 uy = this%v%x(k,1,1,1)
124 uz = this%w%x(k,1,1,1)
126 normal_xyz = this%coef%get_normal(idx(1), idx(2), idx(3), idx(4), &
128 vn = ux*normal_xyz(1) + uy*normal_xyz(2) + uz*normal_xyz(3)
129 s0 = 0.5_rp*(1.0_rp - tanh(vn / (this%uinf * this%delta)))
131 x(k) = -0.5*(ux*ux+uy*uy+uz*uz)*s0
140 integer,
intent(in) :: n
141 real(kind=
rp),
intent(inout),
dimension(n) :: x
142 real(kind=
rp),
intent(inout),
dimension(n) :: y
143 real(kind=
rp),
intent(inout),
dimension(n) :: z
145 logical,
intent(in),
optional :: strong
153 type(c_ptr),
intent(inout) :: x_d
155 logical,
intent(in),
optional :: strong
156 type(c_ptr),
intent(inout) :: strm
159 if (
present(strong))
then
165 if (strong_ .and. this%msk(0) .gt. 0)
then
167 this%normal_x_d, this%normal_y_d, this%normal_z_d, &
168 this%u%x_d, this%v%x_d, this%w%x_d, &
169 this%uinf, this%delta, &
180 type(c_ptr),
intent(inout) :: x_d
181 type(c_ptr),
intent(inout) :: y_d
182 type(c_ptr),
intent(inout) :: z_d
184 logical,
intent(in),
optional :: strong
185 type(c_ptr),
intent(inout) :: strm
201 if (c_associated(this%normal_x_d))
then
203 this%normal_x_d = c_null_ptr
206 if (c_associated(this%normal_y_d))
then
208 this%normal_y_d = c_null_ptr
211 if (c_associated(this%normal_z_d))
then
213 this%normal_z_d = c_null_ptr
221 logical,
optional,
intent(in) :: only_facets
222 real(kind=
rp),
allocatable :: temp_x(:)
223 real(kind=
rp),
allocatable :: temp_y(:)
224 real(kind=
rp),
allocatable :: temp_z(:)
226 integer :: i, m, k, facet, idx(4)
227 real(kind=
rp) :: normal_xyz(3)
229 if (
present(only_facets))
then
230 if (only_facets .eqv. .false.)
then
231 call neko_error(
"For dong_outflow_t, only_facets has to be true.")
235 call this%finalize_base(.true.)
241 call device_alloc(this%normal_x_d, c_sizeof(dummy)*this%msk(0))
242 call device_alloc(this%normal_y_d, c_sizeof(dummy)*this%msk(0))
243 call device_alloc(this%normal_z_d, c_sizeof(dummy)*this%msk(0))
250 facet = this%facet(i)
253 this%coef%get_normal(idx(1), idx(2), idx(3), idx(4), facet)
254 temp_x(i) = normal_xyz(1)
255 temp_y(i) = normal_xyz(2)
256 temp_z(i) = normal_xyz(3)
264 deallocate( temp_x, temp_y, temp_z)
__inline__ __device__ void nonlinear_index(const int idx, const int lx, int *index)
Copy data between host and device (or device and device)
Retrieves a parameter by name or assigns a provided default value. In the latter case also adds the m...
Retrieves a parameter by name or throws an error.
Defines a boundary condition.
subroutine, public device_dong_outflow_apply_scalar(msk, x, normal_x, normal_y, normal_z, u, v, w, uinf, delta, m, strm)
Device abstraction, common interface for various accelerators.
integer, parameter, public host_to_device
subroutine, public device_free(x_d)
Deallocate memory on the device.
subroutine, public device_alloc(x_d, s)
Allocate memory on the device.
Defines a dirichlet boundary condition.
Defines a mapping of the degrees of freedom.
Defines a dong outflow condition.
subroutine dong_outflow_apply_vector_dev(this, x_d, y_d, z_d, time, strong, strm)
Boundary condition apply for a generic Dirichlet condition to vectors x, y and z (device version)
subroutine dong_outflow_apply_vector(this, x, y, z, n, time, strong)
Boundary condition apply for a generic Dirichlet condition to vectors x, y and z.
subroutine dong_outflow_apply_scalar_dev(this, x_d, time, strong, strm)
Boundary condition apply for a generic Dirichlet condition to a vector x (device version)
subroutine dong_outflow_free(this)
Destructor.
subroutine dong_outflow_apply_scalar(this, x, n, time, strong)
Boundary condition apply for a generic Dirichlet condition to a vector x.
subroutine dong_outflow_init(this, coef, json)
Constructor.
subroutine dong_outflow_finalize(this, only_facets)
Finalize.
Utilities for retrieving parameters from the case files.
integer, parameter neko_bcknd_device
integer, parameter, public c_rp
integer, parameter, public rp
Global precision used in computations.
Defines a registry for storing solution fields.
type(registry_t), target, public neko_registry
Global field registry.
Module with things related to the simulation time.
Base type for a boundary condition.
Coefficients defined on a given (mesh, ) tuple. Arrays use indices (i,j,k,e): element e,...
Generic Dirichlet boundary condition on .
Dong outflow condition Follows "A Convective-like Energy-Stable Open Boundary Condition for Simulati...
A struct that contains all info about the time, expand as needed.