Neko 0.9.99
A portable framework for high-order spectral element flow simulations
Loading...
Searching...
No Matches
blasius.f90
Go to the documentation of this file.
1! Copyright (c) 2021, 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!
34module blasius
35 use num_types
36 use coefs, only : coef_t
37 use utils
38 use device
40 use flow_profile
41 use, intrinsic :: iso_fortran_env
42 use, intrinsic :: iso_c_binding
43 use bc, only : bc_t
44 implicit none
45 private
46
48 type, public, extends(bc_t) :: blasius_t
49 real(kind=rp), dimension(3) :: uinf = (/0d0, 0d0, 0d0 /)
50 real(kind=rp) :: delta
51 procedure(blasius_profile), nopass, pointer :: bla => null()
52 type(c_ptr), private :: blax_d = c_null_ptr
53 type(c_ptr), private :: blay_d = c_null_ptr
54 type(c_ptr), private :: blaz_d = c_null_ptr
55 contains
56 procedure, pass(this) :: apply_scalar => blasius_apply_scalar
57 procedure, pass(this) :: apply_vector => blasius_apply_vector
58 procedure, pass(this) :: apply_scalar_dev => blasius_apply_scalar_dev
59 procedure, pass(this) :: apply_vector_dev => blasius_apply_vector_dev
60 procedure, pass(this) :: set_params => blasius_set_params
62 procedure, pass(this) :: free => blasius_free
63 end type blasius_t
64
65contains
66
67 subroutine blasius_free(this)
68 class(blasius_t), target, intent(inout) :: this
69
70 call this%free_base()
71 nullify(this%bla)
72
73 if (c_associated(this%blax_d)) then
74 call device_free(this%blax_d)
75 end if
76
77 if (c_associated(this%blay_d)) then
78 call device_free(this%blay_d)
79 end if
80
81 if (c_associated(this%blaz_d)) then
82 call device_free(this%blaz_d)
83 end if
84
85 end subroutine blasius_free
86
88 subroutine blasius_apply_scalar(this, x, n, t, tstep)
89 class(blasius_t), intent(inout) :: this
90 integer, intent(in) :: n
91 real(kind=rp), intent(inout), dimension(n) :: x
92 real(kind=rp), intent(in), optional :: t
93 integer, intent(in), optional :: tstep
94 end subroutine blasius_apply_scalar
95
97 subroutine blasius_apply_scalar_dev(this, x_d, t, tstep)
98 class(blasius_t), intent(inout), target :: this
99 type(c_ptr) :: x_d
100 real(kind=rp), intent(in), optional :: t
101 integer, intent(in), optional :: tstep
102 end subroutine blasius_apply_scalar_dev
103
105 subroutine blasius_apply_vector(this, x, y, z, n, t, tstep)
106 class(blasius_t), intent(inout) :: this
107 integer, intent(in) :: n
108 real(kind=rp), intent(inout), dimension(n) :: x
109 real(kind=rp), intent(inout), dimension(n) :: y
110 real(kind=rp), intent(inout), dimension(n) :: z
111 real(kind=rp), intent(in), optional :: t
112 integer, intent(in), optional :: tstep
113 integer :: i, m, k, idx(4), facet
114
115 associate(xc => this%coef%dof%x, yc => this%coef%dof%y, &
116 zc => this%coef%dof%z, nx => this%coef%nx, ny => this%coef%ny, &
117 nz => this%coef%nz, lx => this%coef%Xh%lx)
118 m = this%msk(0)
119 do i = 1, m
120 k = this%msk(i)
121 facet = this%facet(i)
122 idx = nonlinear_index(k, lx, lx, lx)
123 select case(facet)
124 case(1,2)
125 x(k) = this%bla(zc(idx(1), idx(2), idx(3), idx(4)), &
126 this%delta, this%uinf(1))
127 y(k) = 0.0_rp
128 z(k) = 0.0_rp
129 case(3,4)
130 x(k) = 0.0_rp
131 y(k) = this%bla(xc(idx(1), idx(2), idx(3), idx(4)), &
132 this%delta, this%uinf(2))
133 z(k) = 0.0_rp
134 case(5,6)
135 x(k) = 0.0_rp
136 y(k) = 0.0_rp
137 z(k) = this%bla(yc(idx(1), idx(2), idx(3), idx(4)), &
138 this%delta, this%uinf(3))
139 end select
140 end do
141 end associate
142 end subroutine blasius_apply_vector
143
145 subroutine blasius_apply_vector_dev(this, x_d, y_d, z_d, t, tstep)
146 class(blasius_t), intent(inout), target :: this
147 type(c_ptr) :: x_d
148 type(c_ptr) :: y_d
149 type(c_ptr) :: z_d
150 real(kind=rp), intent(in), optional :: t
151 integer, intent(in), optional :: tstep
152 integer :: i, m, k, idx(4), facet
153 integer(c_size_t) :: s
154 real(kind=rp), allocatable :: bla_x(:), bla_y(:), bla_z(:)
155
156 associate(xc => this%coef%dof%x, yc => this%coef%dof%y, &
157 zc => this%coef%dof%z, nx => this%coef%nx, ny => this%coef%ny, &
158 nz => this%coef%nz, lx => this%coef%Xh%lx , blax_d => this%blax_d,&
159 blay_d => this%blay_d, blaz_d => this%blaz_d)
160
161 m = this%msk(0)
162
163
164 ! Pretabulate values during first call to apply
165 if (.not. c_associated(blax_d)) then
166 allocate(bla_x(m), bla_y(m), bla_z(m)) ! Temp arrays
167
168 if (rp .eq. real32) then
169 s = m * 4
170 else if (rp .eq. real64) then
171 s = m * 8
172 end if
173
174 call device_alloc(blax_d, s)
175 call device_alloc(blay_d, s)
176 call device_alloc(blaz_d, s)
177
178 do i = 1, m
179 k = this%msk(i)
180 facet = this%facet(i)
181 idx = nonlinear_index(k, lx, lx, lx)
182 select case(facet)
183 case(1,2)
184 bla_x(i) = this%bla(zc(idx(1), idx(2), idx(3), idx(4)), &
185 this%delta, this%uinf(1))
186 bla_y(i) = 0.0_rp
187 bla_z(i) = 0.0_rp
188 case(3,4)
189 bla_x(i) = 0.0_rp
190 bla_y(i) = this%bla(xc(idx(1), idx(2), idx(3), idx(4)), &
191 this%delta, this%uinf(2))
192 bla_z(i) = 0.0_rp
193 case(5,6)
194 bla_x(i) = 0.0_rp
195 bla_y(i) = 0.0_rp
196 bla_z(i) = this%bla(yc(idx(1), idx(2), idx(3), idx(4)), &
197 this%delta, this%uinf(3))
198 end select
199 end do
200
201 call device_memcpy(bla_x, blax_d, m, host_to_device, sync=.false.)
202 call device_memcpy(bla_y, blay_d, m, host_to_device, sync=.false.)
203 call device_memcpy(bla_z, blaz_d, m, host_to_device, sync=.true.)
204
205 deallocate(bla_x, bla_y, bla_z)
206 end if
207
208 call device_inhom_dirichlet_apply_vector(this%msk_d, x_d, y_d, z_d, &
209 blax_d, blay_d, blaz_d, m)
210
211 end associate
212
213 end subroutine blasius_apply_vector_dev
214
216 subroutine blasius_set_params(this, uinf, delta, type)
217 class(blasius_t), intent(inout) :: this
218 real(kind=rp), intent(in) :: uinf(3)
219 real(kind=rp), intent(in) :: delta
220 character(len=*) :: type
221 this%delta = delta
222 this%uinf = uinf
223
224 select case(trim(type))
225 case('linear')
226 this%bla => blasius_linear
227 case('quadratic')
228 this%bla => blasius_quadratic
229 case('cubic')
230 this%bla => blasius_cubic
231 case('quartic')
232 this%bla => blasius_quartic
233 case('sin')
234 this%bla => blasius_sin
235 case default
236 call neko_error('Invalid Blasius approximation')
237 end select
238 end subroutine blasius_set_params
239
240end module blasius
__device__ void nonlinear_index(const int idx, const int lx, int *index)
Abstract interface for computing a Blasius flow profile.
Defines a boundary condition.
Definition bc.f90:34
Defines a Blasius profile dirichlet condition.
Definition blasius.f90:34
subroutine blasius_apply_vector(this, x, y, z, n, t, tstep)
Apply blasius conditions (vector valued)
Definition blasius.f90:106
subroutine blasius_apply_vector_dev(this, x_d, y_d, z_d, t, tstep)
Apply blasius conditions (vector valued) (device version)
Definition blasius.f90:146
subroutine blasius_apply_scalar_dev(this, x_d, t, tstep)
No-op scalar apply (device version)
Definition blasius.f90:98
subroutine blasius_apply_scalar(this, x, n, t, tstep)
No-op scalar apply.
Definition blasius.f90:89
subroutine blasius_free(this)
Definition blasius.f90:68
subroutine blasius_set_params(this, uinf, delta, type)
Set Blasius parameters.
Definition blasius.f90:217
Coefficients.
Definition coef.f90:34
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:185
Defines a flow profile.
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:51
Blasius profile for inlet (vector valued)
Definition blasius.f90:48
Coefficients defined on a given (mesh, ) tuple. Arrays use indices (i,j,k,e): element e,...
Definition coef.f90:55