Neko  0.8.99
A portable framework for high-order spectral element flow simulations
flow_ic.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 flow_ic
35  use num_types, only : rp
36  use gather_scatter, only : gs_t, gs_op_add
37  use neko_config, only : neko_bcknd_device
41  use field, only : field_t
42  use utils, only : neko_error
43  use coefs, only : coef_t
44  use math, only : col2, cfill, cfill_mask
46  use user_intf, only : useric
47  use json_module, only : json_file
48  use json_utils, only: json_get
49  use point_zone, only: point_zone_t
51  implicit none
52  private
53 
54  interface set_flow_ic
55  module procedure set_flow_ic_int, set_flow_ic_usr
56  end interface set_flow_ic
57 
58  public :: set_flow_ic
59 
60 contains
61 
63  subroutine set_flow_ic_int(u, v, w, p, coef, gs, type, params)
64  type(field_t), intent(inout) :: u
65  type(field_t), intent(inout) :: v
66  type(field_t), intent(inout) :: w
67  type(field_t), intent(inout) :: p
68  type(coef_t), intent(in) :: coef
69  type(gs_t), intent(inout) :: gs
70  character(len=*) :: type
71  type(json_file), intent(inout) :: params
72  real(kind=rp) :: delta
73  real(kind=rp), allocatable :: uinf(:)
74  real(kind=rp), allocatable :: zone_value(:)
75  character(len=:), allocatable :: blasius_approximation
76  character(len=:), allocatable :: zone_name
77 
78  if (trim(type) .eq. 'uniform') then
79  call json_get(params, 'case.fluid.initial_condition.value', uinf)
80  call set_flow_ic_uniform(u, v, w, uinf)
81  else if (trim(type) .eq. 'blasius') then
82  call json_get(params, 'case.fluid.blasius.delta', delta)
83  call json_get(params, 'case.fluid.blasius.approximation', &
84  blasius_approximation)
85  call json_get(params, 'case.fluid.blasius.freestream_velocity', uinf)
86  call set_flow_ic_blasius(u, v, w, delta, uinf, blasius_approximation)
87  else if (trim(type) .eq. 'point_zone') then
88  call json_get(params, 'case.fluid.initial_condition.base_value', uinf)
89  call json_get(params, 'case.fluid.initial_condition.zone_name', &
90  zone_name)
91  call json_get(params, 'case.fluid.initial_condition.zone_value', &
92  zone_value)
93  call set_flow_ic_point_zone(u, v, w, uinf, zone_name, zone_value)
94  else
95  call neko_error('Invalid initial condition')
96  end if
97 
98  call set_flow_ic_common(u, v, w, p, coef, gs)
99 
100  end subroutine set_flow_ic_int
101 
103  subroutine set_flow_ic_usr(u, v, w, p, coef, gs, usr_ic, params)
104  type(field_t), intent(inout) :: u
105  type(field_t), intent(inout) :: v
106  type(field_t), intent(inout) :: w
107  type(field_t), intent(inout) :: p
108  type(coef_t), intent(in) :: coef
109  type(gs_t), intent(inout) :: gs
110  procedure(useric) :: usr_ic
111  type(json_file), intent(inout) :: params
112 
113  call usr_ic(u, v, w, p, params)
114 
115  call set_flow_ic_common(u, v, w, p, coef, gs)
116 
117  end subroutine set_flow_ic_usr
118 
119  subroutine set_flow_ic_common(u, v, w, p, coef, gs)
120  type(field_t), intent(inout) :: u
121  type(field_t), intent(inout) :: v
122  type(field_t), intent(inout) :: w
123  type(field_t), intent(inout) :: p
124  type(coef_t), intent(in) :: coef
125  type(gs_t), intent(inout) :: gs
126  integer :: n
127 
128  n = u%dof%size()
129 
130  if (neko_bcknd_device .eq. 1) then
131  call device_memcpy(u%x, u%x_d, n, &
132  host_to_device, sync=.false.)
133  call device_memcpy(v%x, v%x_d, n, &
134  host_to_device, sync=.false.)
135  call device_memcpy(w%x, w%x_d, n, &
136  host_to_device, sync=.false.)
137  end if
138 
139  ! Ensure continuity across elements for initial conditions
140  call gs%op(u%x, u%dof%size(), gs_op_add)
141  call gs%op(v%x, v%dof%size(), gs_op_add)
142  call gs%op(w%x, w%dof%size(), gs_op_add)
143 
144  if (neko_bcknd_device .eq. 1) then
145  call device_col2(u%x_d, coef%mult_d, u%dof%size())
146  call device_col2(v%x_d, coef%mult_d, v%dof%size())
147  call device_col2(w%x_d, coef%mult_d, w%dof%size())
148  else
149  call col2(u%x, coef%mult, u%dof%size())
150  call col2(v%x, coef%mult, v%dof%size())
151  call col2(w%x, coef%mult, w%dof%size())
152  end if
153 
154  end subroutine set_flow_ic_common
155 
157  subroutine set_flow_ic_uniform(u, v, w, uinf)
158  type(field_t), intent(inout) :: u
159  type(field_t), intent(inout) :: v
160  type(field_t), intent(inout) :: w
161  real(kind=rp), intent(in) :: uinf(3)
162  integer :: n
163  u = uinf(1)
164  v = uinf(2)
165  w = uinf(3)
166  n = u%dof%size()
167  if (neko_bcknd_device .eq. 1) then
168  call cfill(u%x, uinf(1), n)
169  call cfill(v%x, uinf(2), n)
170  call cfill(w%x, uinf(3), n)
171  end if
172 
173  end subroutine set_flow_ic_uniform
174 
177  subroutine set_flow_ic_blasius(u, v, w, delta, uinf, type)
178  type(field_t), intent(inout) :: u
179  type(field_t), intent(inout) :: v
180  type(field_t), intent(inout) :: w
181  real(kind=rp), intent(in) :: delta
182  real(kind=rp), intent(in) :: uinf(3)
183  character(len=*), intent(in) :: type
184  procedure(blasius_profile), pointer :: bla => null()
185  integer :: i
186 
187  select case(trim(type))
188  case('linear')
189  bla => blasius_linear
190  case('quadratic')
191  bla => blasius_quadratic
192  case('cubic')
193  bla => blasius_cubic
194  case('quartic')
195  bla => blasius_quartic
196  case('sin')
197  bla => blasius_sin
198  case default
199  call neko_error('Invalid Blasius approximation')
200  end select
201 
202  if ((uinf(1) .gt. 0.0_rp) .and. (uinf(2) .eq. 0.0_rp) &
203  .and. (uinf(3) .eq. 0.0_rp)) then
204  do i = 1, u%dof%size()
205  u%x(i,1,1,1) = bla(u%dof%z(i,1,1,1), delta, uinf(1))
206  v%x(i,1,1,1) = 0.0_rp
207  w%x(i,1,1,1) = 0.0_rp
208  end do
209  else if ((uinf(1) .eq. 0.0_rp) .and. (uinf(2) .gt. 0.0_rp) &
210  .and. (uinf(3) .eq. 0.0_rp)) then
211  do i = 1, u%dof%size()
212  u%x(i,1,1,1) = 0.0_rp
213  v%x(i,1,1,1) = bla(u%dof%x(i,1,1,1), delta, uinf(2))
214  w%x(i,1,1,1) = 0.0_rp
215  end do
216  else if ((uinf(1) .eq. 0.0_rp) .and. (uinf(2) .eq. 0.0_rp) &
217  .and. (uinf(3) .gt. 0.0_rp)) then
218  do i = 1, u%dof%size()
219  u%x(i,1,1,1) = 0.0_rp
220  v%x(i,1,1,1) = 0.0_rp
221  w%x(i,1,1,1) = bla(u%dof%y(i,1,1,1), delta, uinf(3))
222  end do
223  end if
224 
225  end subroutine set_flow_ic_blasius
226 
236  subroutine set_flow_ic_point_zone(u, v, w, base_value, zone_name, zone_value)
237  type(field_t), intent(inout) :: u
238  type(field_t), intent(inout) :: v
239  type(field_t), intent(inout) :: w
240  real(kind=rp), intent(in), dimension(3) :: base_value
241  character(len=*), intent(in) :: zone_name
242  real(kind=rp), intent(in) :: zone_value(:)
243 
244  ! Internal variables
245  class(point_zone_t), pointer :: zone
246  integer :: size
247 
248  call set_flow_ic_uniform(u, v, w, base_value)
249  size = u%dof%size()
250 
251  zone => neko_point_zone_registry%get_point_zone(trim(zone_name))
252 
253  call cfill_mask(u%x, zone_value(1), size, zone%mask, zone%size)
254  call cfill_mask(v%x, zone_value(2), size, zone%mask, zone%size)
255  call cfill_mask(w%x, zone_value(3), size, zone%mask, zone%size)
256 
257  end subroutine set_flow_ic_point_zone
258 
259 end module flow_ic
Copy data between host and device (or device and device)
Definition: device.F90:51
Abstract interface for computing a Blasius flow profile.
Retrieves a parameter by name or throws an error.
Definition: json_utils.f90:44
Abstract interface for user defined initial conditions.
Definition: user_intf.f90:57
Coefficients.
Definition: coef.f90:34
subroutine, public device_col2(a_d, b_d, n)
Vector multiplication .
subroutine, public device_cfill_mask(a_d, c, size, mask_d, mask_size)
Fill a constant to a masked vector. .
subroutine, public device_cfill(a_d, c, n)
Set all elements to a constant c .
Device abstraction, common interface for various accelerators.
Definition: device.F90:34
integer, parameter, public host_to_device
Definition: device.F90:47
Defines a field.
Definition: field.f90:34
Initial flow condition.
Definition: flow_ic.f90:34
subroutine set_flow_ic_usr(u, v, w, p, coef, gs, usr_ic, params)
Set intial flow condition (user defined)
Definition: flow_ic.f90:104
subroutine set_flow_ic_point_zone(u, v, w, base_value, zone_name, zone_value)
Set the initial condition of the flow based on a point zone.
Definition: flow_ic.f90:237
subroutine set_flow_ic_int(u, v, w, p, coef, gs, type, params)
Set initial flow condition (builtin)
Definition: flow_ic.f90:64
subroutine set_flow_ic_uniform(u, v, w, uinf)
Uniform initial condition.
Definition: flow_ic.f90:158
subroutine set_flow_ic_common(u, v, w, p, coef, gs)
Definition: flow_ic.f90:120
subroutine set_flow_ic_blasius(u, v, w, delta, uinf, type)
Set a Blasius profile as initial condition.
Definition: flow_ic.f90:178
Defines a flow profile.
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 .
Gather-scatter.
Utilities for retrieving parameters from the case files.
Definition: json_utils.f90:34
Definition: math.f90:60
subroutine, public cfill(a, c, n)
Set all elements to a constant c .
Definition: math.f90:314
subroutine, public col2(a, b, n)
Vector multiplication .
Definition: math.f90:689
subroutine, public cfill_mask(a, c, size, mask, mask_size)
Fill a constant to a masked vector. .
Definition: math.f90:263
Build configurations.
Definition: neko_config.f90:34
integer, parameter neko_bcknd_device
Definition: neko_config.f90:44
integer, parameter, public rp
Global precision used in computations.
Definition: num_types.f90:12
type(point_zone_registry_t), target, public neko_point_zone_registry
Global point_zone registry.
Interfaces for user interaction with NEKO.
Definition: user_intf.f90:34
Utilities.
Definition: utils.f90:35
Coefficients defined on a given (mesh, ) tuple. Arrays use indices (i,j,k,e): element e,...
Definition: coef.f90:55
Base abstract type for point zones.
Definition: point_zone.f90:47