41 use,
intrinsic :: iso_fortran_env
42 use,
intrinsic :: iso_c_binding
44 use json_module,
only : json_file
53 real(kind=
rp),
dimension(3) :: uinf = [0d0, 0d0, 0d0]
54 real(kind=
rp) :: delta
56 type(c_ptr),
private :: blax_d = c_null_ptr
57 type(c_ptr),
private :: blay_d = c_null_ptr
58 type(c_ptr),
private :: blaz_d = c_null_ptr
68 procedure, pass(this) :: init_from_components => &
82 class(
blasius_t),
intent(inout),
target :: this
83 type(
coef_t),
intent(in) :: coef
84 type(json_file),
intent(inout) :: json
85 real(kind=
rp) :: delta
86 real(kind=
rp),
allocatable :: uinf(:)
87 character(len=:),
allocatable :: approximation
89 call this%init_base(coef)
92 call json_get(json,
'approximation', approximation)
93 call json_get(json,
'freestream_velocity', uinf)
95 if (
size(uinf) .ne. 3)
then
96 call neko_error(
"The uinf keyword for the blasius profile should be an &
100 call this%init_from_components(coef, delta, uinf, approximation)
111 class(
blasius_t),
intent(inout),
target :: this
112 type(
coef_t),
intent(in) :: coef
113 real(kind=
rp) :: delta
114 real(kind=
rp) :: uinf(3)
115 character(len=*) :: approximation
117 call this%init_base(coef)
122 select case (trim(approximation))
134 call neko_error(
'Invalid Blasius approximation')
139 class(
blasius_t),
target,
intent(inout) :: this
141 call this%free_base()
144 if (c_associated(this%blax_d))
then
148 if (c_associated(this%blay_d))
then
152 if (c_associated(this%blaz_d))
then
161 integer,
intent(in) :: n
162 real(kind=
rp),
intent(inout),
dimension(n) :: x
163 real(kind=
rp),
intent(in),
optional :: t
164 integer,
intent(in),
optional :: tstep
165 logical,
intent(in),
optional :: strong
170 class(
blasius_t),
intent(inout),
target :: this
172 real(kind=
rp),
intent(in),
optional :: t
173 integer,
intent(in),
optional :: tstep
174 logical,
intent(in),
optional :: strong
180 integer,
intent(in) :: n
181 real(kind=
rp),
intent(inout),
dimension(n) :: x
182 real(kind=
rp),
intent(inout),
dimension(n) :: y
183 real(kind=
rp),
intent(inout),
dimension(n) :: z
184 real(kind=
rp),
intent(in),
optional :: t
185 integer,
intent(in),
optional :: tstep
186 logical,
intent(in),
optional :: strong
187 integer :: i, m, k, idx(4), facet
188 logical :: strong_ = .true.
190 if (
present(strong)) strong_ = strong
192 associate(xc => this%coef%dof%x, yc => this%coef%dof%y, &
193 zc => this%coef%dof%z, nx => this%coef%nx, ny => this%coef%ny, &
194 nz => this%coef%nz, lx => this%coef%Xh%lx)
199 facet = this%facet(i)
203 x(k) = this%bla(zc(idx(1), idx(2), idx(3), idx(4)), &
204 this%delta, this%uinf(1))
209 y(k) = this%bla(xc(idx(1), idx(2), idx(3), idx(4)), &
210 this%delta, this%uinf(2))
215 z(k) = this%bla(yc(idx(1), idx(2), idx(3), idx(4)), &
216 this%delta, this%uinf(3))
225 class(
blasius_t),
intent(inout),
target :: this
229 real(kind=rp),
intent(in),
optional :: t
230 integer,
intent(in),
optional :: tstep
231 logical,
intent(in),
optional :: strong
232 integer :: i, m, k, idx(4), facet
233 integer(c_size_t) :: s
234 real(kind=rp),
allocatable :: bla_x(:), bla_y(:), bla_z(:)
235 logical :: strong_ = .true.
237 if (
present(strong)) strong_ = strong
239 associate(xc => this%coef%dof%x, yc => this%coef%dof%y, &
240 zc => this%coef%dof%z, nx => this%coef%nx, ny => this%coef%ny, &
241 nz => this%coef%nz, lx => this%coef%Xh%lx , &
242 blax_d => this%blax_d, blay_d => this%blay_d, &
243 blaz_d => this%blaz_d)
249 if (.not. c_associated(blax_d) .and. strong_ .and. this%msk(0) .gt. 0)
then
250 allocate(bla_x(m), bla_y(m), bla_z(m))
252 if (rp .eq. real32)
then
254 else if (rp .eq. real64)
then
258 call device_alloc(blax_d, s)
259 call device_alloc(blay_d, s)
260 call device_alloc(blaz_d, s)
264 facet = this%facet(i)
268 bla_x(i) = this%bla(zc(idx(1), idx(2), idx(3), idx(4)), &
269 this%delta, this%uinf(1))
274 bla_y(i) = this%bla(xc(idx(1), idx(2), idx(3), idx(4)), &
275 this%delta, this%uinf(2))
280 bla_z(i) = this%bla(yc(idx(1), idx(2), idx(3), idx(4)), &
281 this%delta, this%uinf(3))
285 call device_memcpy(bla_x, blax_d, m, host_to_device, sync = .false.)
286 call device_memcpy(bla_y, blay_d, m, host_to_device, sync = .false.)
287 call device_memcpy(bla_z, blaz_d, m, host_to_device, sync = .true.)
289 deallocate(bla_x, bla_y, bla_z)
292 if (strong_ .and. this%msk(0) .gt. 0)
then
293 call device_inhom_dirichlet_apply_vector(this%msk_d, x_d, y_d, z_d, &
294 blax_d, blay_d, blaz_d, m)
304 real(kind=rp),
intent(in) :: uinf(3)
305 real(kind=rp),
intent(in) :: delta
306 character(len=*) :: type
310 select case (trim(type))
312 this%bla => blasius_linear
314 this%bla => blasius_quadratic
316 this%bla => blasius_cubic
318 this%bla => blasius_quartic
320 this%bla => blasius_sin
322 call neko_error(
'Invalid Blasius approximation')
328 class(
blasius_t),
target,
intent(inout) :: this
330 call this%finalize_base()
__device__ void nonlinear_index(const int idx, const int lx, int *index)
Copy data between host and device (or device and device)
Abstract interface for computing a Blasius flow profile.
Retrieves a parameter by name or throws an error.
Defines a boundary condition.
Defines a Blasius profile dirichlet condition.
subroutine blasius_apply_scalar(this, x, n, t, tstep, strong)
No-op scalar apply.
subroutine blasius_init(this, coef, json)
Constructor.
subroutine blasius_apply_scalar_dev(this, x_d, t, tstep, strong)
No-op scalar apply (device version)
subroutine blasius_init_from_components(this, coef, delta, uinf, approximation)
Constructor from components.
subroutine blasius_apply_vector_dev(this, x_d, y_d, z_d, t, tstep, strong)
Apply blasius conditions (vector valued) (device version)
subroutine blasius_free(this)
subroutine blasius_apply_vector(this, x, y, z, n, t, tstep, strong)
Apply blasius conditions (vector valued)
subroutine blasius_finalize(this)
Finalize.
subroutine blasius_set_params(this, uinf, delta, type)
Set Blasius parameters.
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.
real(kind=rp) function, public blasius_quadratic(y, delta, u)
Quadratic approximate Blasius Profile .
real(kind=rp) function, public blasius_quartic(y, delta, u)
Quartic approximate Blasius Profile .
real(kind=rp) function, public blasius_sin(y, delta, u)
Sinusoidal approximate Blasius Profile .
real(kind=rp) function, public blasius_cubic(y, delta, u)
Cubic approximate Blasius Profile .
real(kind=rp) function, public blasius_linear(y, delta, u)
Linear approximate Blasius profile .
Utilities for retrieving parameters from the case files.
integer, parameter, public rp
Global precision used in computations.
Base type for a boundary condition.
Blasius profile for inlet (vector valued).
Coefficients defined on a given (mesh, ) tuple. Arrays use indices (i,j,k,e): element e,...