Loading [MathJax]/extensions/tex2jax.js
Neko 0.9.99
A portable framework for high-order spectral element flow simulations
All Classes Namespaces Files Functions Variables Typedefs Enumerator Macros Pages
dong_outflow.f90
Go to the documentation of this file.
1! Copyright (c) 2025, 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, only : dirichlet_t
38 use num_types, only : rp, c_rp
39 use bc, only : bc_t
40 use field, only : field_t
41 use dofmap, only : dofmap_t
42 use coefs, only : coef_t
43 use utils, only : nonlinear_index
46 use, intrinsic :: iso_c_binding, only : c_ptr, c_sizeof, c_null_ptr
47 use json_module, only : json_file
49 implicit none
50 private
51
57 type, public, extends(bc_t) :: dong_outflow_t
58 type(field_t), pointer :: u
59 type(field_t), pointer :: v
60 type(field_t), pointer :: w
61 real(kind=rp) :: delta
62 real(kind=rp) :: uinf
63 type(c_ptr) :: normal_x_d = c_null_ptr
64 type(c_ptr) :: normal_y_d = c_null_ptr
65 type(c_ptr) :: normal_z_d = c_null_ptr
66 contains
67 procedure, pass(this) :: apply_scalar => dong_outflow_apply_scalar
68 procedure, pass(this) :: apply_vector => dong_outflow_apply_vector
69 procedure, pass(this) :: apply_scalar_dev => dong_outflow_apply_scalar_dev
70 procedure, pass(this) :: apply_vector_dev => dong_outflow_apply_vector_dev
72 procedure, pass(this) :: init => dong_outflow_init
74 procedure, pass(this) :: free => dong_outflow_free
76 procedure, pass(this) :: finalize => dong_outflow_finalize
77 end type dong_outflow_t
78
79contains
83 subroutine dong_outflow_init(this, coef, json)
84 class(dong_outflow_t), target, intent(inout) :: this
85 type(coef_t), intent(in) :: coef
86 type(json_file), intent(inout) :: json
87 call this%free()
88 call this%init_base(coef)
89
90 call json_get_or_default(json, 'delta', &
91 this%delta, 0.01_rp)
92 call json_get_or_default(json, 'velocity_scale', &
93 this%uinf, 1.0_rp)
94
95 end subroutine dong_outflow_init
96
99 subroutine dong_outflow_apply_scalar(this, x, n, t, tstep, strong)
100 class(dong_outflow_t), intent(inout) :: this
101 integer, intent(in) :: n
102 real(kind=rp), intent(inout), dimension(n) :: x
103 real(kind=rp), intent(in), optional :: t
104 integer, intent(in), optional :: tstep
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)
108 logical :: strong_ = .true.
109
110 if (present(strong)) strong_ = strong
111
112 if (strong_) then
113 m = this%msk(0)
114 do i = 1, m
115 k = this%msk(i)
116 facet = this%facet(i)
117 ux = this%u%x(k,1,1,1)
118 uy = this%v%x(k,1,1,1)
119 uz = this%w%x(k,1,1,1)
120 idx = nonlinear_index(k, this%Xh%lx, this%Xh%lx, this%Xh%lx)
121 normal_xyz = this%coef%get_normal(idx(1), idx(2), idx(3), idx(4), &
122 facet)
123 vn = ux*normal_xyz(1) + uy*normal_xyz(2) + uz*normal_xyz(3)
124 s0 = 0.5_rp*(1.0_rp - tanh(vn / (this%uinf * this%delta)))
125
126 x(k) = -0.5*(ux*ux+uy*uy+uz*uz)*s0
127 end do
128 end if
129 end subroutine dong_outflow_apply_scalar
130
133 subroutine dong_outflow_apply_vector(this, x, y, z, n, t, tstep, strong)
134 class(dong_outflow_t), intent(inout) :: this
135 integer, intent(in) :: n
136 real(kind=rp), intent(inout), dimension(n) :: x
137 real(kind=rp), intent(inout), dimension(n) :: y
138 real(kind=rp), intent(inout), dimension(n) :: z
139 real(kind=rp), intent(in), optional :: t
140 integer, intent(in), optional :: tstep
141 logical, intent(in), optional :: strong
142
143 end subroutine dong_outflow_apply_vector
144
147 subroutine dong_outflow_apply_scalar_dev(this, x_d, t, tstep, strong)
148 class(dong_outflow_t), intent(inout), target :: this
149 type(c_ptr) :: x_d
150 real(kind=rp), intent(in), optional :: t
151 integer, intent(in), optional :: tstep
152 logical, intent(in), optional :: strong
153 logical :: strong_ = .true.
154
155 if (present(strong)) strong_ = strong
156
157 if (strong_ .and. this%msk(0) .gt. 0) then
158 call device_dong_outflow_apply_scalar(this%msk_d, x_d, &
159 this%normal_x_d, this%normal_y_d, this%normal_z_d, &
160 this%u%x_d, this%v%x_d, this%w%x_d, &
161 this%uinf, this%delta, &
162 this%msk(0))
163 end if
164
165 end subroutine dong_outflow_apply_scalar_dev
166
169 subroutine dong_outflow_apply_vector_dev(this, x_d, y_d, z_d, t, tstep, &
170 strong)
171 class(dong_outflow_t), intent(inout), target :: this
172 type(c_ptr) :: x_d
173 type(c_ptr) :: y_d
174 type(c_ptr) :: z_d
175 real(kind=rp), intent(in), optional :: t
176 integer, intent(in), optional :: tstep
177 logical, intent(in), optional :: strong
178
179 !call device_dong_outflow_apply_vector(this%msk_d, x_d, y_d, z_d, &
180 ! this%g, size(this%msk))
181
182 end subroutine dong_outflow_apply_vector_dev
183
185 subroutine dong_outflow_free(this)
186 class(dong_outflow_t), target, intent(inout) :: this
187
188 call this%free_base
189
190 end subroutine dong_outflow_free
191
193 subroutine dong_outflow_finalize(this)
194 class(dong_outflow_t), target, intent(inout) :: this
195 real(kind=rp), allocatable :: temp_x(:)
196 real(kind=rp), allocatable :: temp_y(:)
197 real(kind=rp), allocatable :: temp_z(:)
198 real(c_rp) :: dummy
199 integer :: i, m, k, facet, idx(4)
200 real(kind=rp) :: normal_xyz(3)
201
202
203 call this%finalize_base(.true.)
204 this%u => neko_field_registry%get_field("u")
205 this%v => neko_field_registry%get_field("v")
206 this%w => neko_field_registry%get_field("w")
207 if ((neko_bcknd_device .eq. 1) .and. (this%msk(0) .gt. 0)) then
208 call device_alloc(this%normal_x_d, c_sizeof(dummy)*this%msk(0))
209 call device_alloc(this%normal_y_d, c_sizeof(dummy)*this%msk(0))
210 call device_alloc(this%normal_z_d, c_sizeof(dummy)*this%msk(0))
211 m = this%msk(0)
212 allocate(temp_x(m))
213 allocate(temp_y(m))
214 allocate(temp_z(m))
215 do i = 1, m
216 k = this%msk(i)
217 facet = this%facet(i)
218 idx = nonlinear_index(k, this%Xh%lx, this%Xh%lx, this%Xh%lx)
219 normal_xyz = &
220 this%coef%get_normal(idx(1), idx(2), idx(3), idx(4), facet)
221 temp_x(i) = normal_xyz(1)
222 temp_y(i) = normal_xyz(2)
223 temp_z(i) = normal_xyz(3)
224 end do
225 call device_memcpy(temp_x, this%normal_x_d, m, host_to_device, &
226 sync = .false.)
227 call device_memcpy(temp_y, this%normal_y_d, m, host_to_device, &
228 sync = .false.)
229 call device_memcpy(temp_z, this%normal_z_d, m, host_to_device, &
230 sync = .true.)
231 deallocate( temp_x, temp_y, temp_z)
232 end if
233 end subroutine dong_outflow_finalize
234
235end 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:65
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.
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:46
subroutine, public device_alloc(x_d, s)
Allocate memory on the device.
Definition device.F90:179
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_dev(this, x_d, y_d, z_d, t, tstep, strong)
Boundary condition apply for a generic Dirichlet condition to vectors x, y and z (device version)
subroutine dong_outflow_finalize(this)
Finalize.
subroutine dong_outflow_apply_scalar_dev(this, x_d, t, tstep, strong)
Boundary condition apply for a generic Dirichlet condition to a vector x (device version)
subroutine dong_outflow_apply_vector(this, x, y, z, n, t, tstep, strong)
Boundary condition apply for a generic Dirichlet condition to vectors x, y and z.
subroutine dong_outflow_apply_scalar(this, x, n, t, tstep, strong)
Boundary condition apply for a generic Dirichlet condition to a vector x.
subroutine dong_outflow_free(this)
Destructor.
subroutine dong_outflow_init(this, coef, json)
Constructor.
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
Utilities for retrieving parameters from the case files.
Build configurations.
integer, parameter neko_bcknd_device
integer, parameter, public c_rp
Definition num_types.f90:13
integer, parameter, public rp
Global precision used in computations.
Definition num_types.f90:12
Utilities.
Definition utils.f90:35
Base type for a boundary condition.
Definition bc.f90:57
Coefficients defined on a given (mesh, ) tuple. Arrays use indices (i,j,k,e): element e,...
Definition coef.f90:55
Generic Dirichlet boundary condition on .
Definition dirichlet.f90:47
Dong outflow condition Follows "A Convective-like Energy-Stable Open Boundary Condition for Simulati...