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