Neko  0.8.1
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 gather_scatter
36  use neko_config
37  use flow_profile
38  use device_math
39  use device
40  use field
41  use utils
42  use coefs
43  use math
44  use user_intf, only : useric
45  use json_module, only : json_file
46  use json_utils, only: json_get
47  implicit none
48  private
49 
50  interface set_flow_ic
51  module procedure set_flow_ic_int, set_flow_ic_usr
52  end interface set_flow_ic
53 
54  public :: set_flow_ic
55 
56 contains
57 
59  subroutine set_flow_ic_int(u, v, w, p, coef, gs, type, params)
60  type(field_t), intent(inout) :: u
61  type(field_t), intent(inout) :: v
62  type(field_t), intent(inout) :: w
63  type(field_t), intent(inout) :: p
64  type(coef_t), intent(in) :: coef
65  type(gs_t), intent(inout) :: gs
66  character(len=*) :: type
67  type(json_file), intent(inout) :: params
68  ! Variables for retrieving json parameters
69  logical :: found
70  real(kind=rp) :: delta
71  real(kind=rp), allocatable :: uinf(:)
72  character(len=:), allocatable :: blasius_approximation
73 
74  if (trim(type) .eq. 'uniform') then
75  call json_get(params, 'case.fluid.initial_condition.value', uinf)
76  call set_flow_ic_uniform(u, v, w, uinf)
77  else if (trim(type) .eq. 'blasius') then
78  call json_get(params, 'case.fluid.blasius.delta', delta)
79  call json_get(params, 'case.fluid.blasius.approximation',&
80  blasius_approximation)
81  call json_get(params, 'case.fluid.blasius.freestream_velocity', uinf)
82  call set_flow_ic_blasius(u, v, w, delta, uinf, blasius_approximation)
83  else
84  call neko_error('Invalid initial condition')
85  end if
86 
87  call set_flow_ic_common(u, v, w, p, coef, gs)
88 
89  end subroutine set_flow_ic_int
90 
92  subroutine set_flow_ic_usr(u, v, w, p, coef, gs, usr_ic, params)
93  type(field_t), intent(inout) :: u
94  type(field_t), intent(inout) :: v
95  type(field_t), intent(inout) :: w
96  type(field_t), intent(inout) :: p
97  type(coef_t), intent(in) :: coef
98  type(gs_t), intent(inout) :: gs
99  procedure(useric) :: usr_ic
100  type(json_file), intent(inout) :: params
101 
102  call usr_ic(u, v, w, p, params)
103 
104  call set_flow_ic_common(u, v, w, p, coef, gs)
105 
106  end subroutine set_flow_ic_usr
107 
108  subroutine set_flow_ic_common(u, v, w, p, coef, gs)
109  type(field_t), intent(inout) :: u
110  type(field_t), intent(inout) :: v
111  type(field_t), intent(inout) :: w
112  type(field_t), intent(inout) :: p
113  type(coef_t), intent(in) :: coef
114  type(gs_t), intent(inout) :: gs
115 
116  if (neko_bcknd_device .eq. 1) then
117  call device_memcpy(u%x, u%x_d, u%dof%size(), &
118  host_to_device, sync=.false.)
119  call device_memcpy(v%x, v%x_d, v%dof%size(), &
120  host_to_device, sync=.false.)
121  call device_memcpy(w%x, w%x_d, w%dof%size(), &
122  host_to_device, sync=.false.)
123  end if
124 
125  ! Ensure continuity across elements for initial conditions
126  call gs%op(u%x, u%dof%size(), gs_op_add)
127  call gs%op(v%x, v%dof%size(), gs_op_add)
128  call gs%op(w%x, w%dof%size(), gs_op_add)
129 
130  if (neko_bcknd_device .eq. 1) then
131  call device_col2(u%x_d, coef%mult_d, u%dof%size())
132  call device_col2(v%x_d, coef%mult_d, v%dof%size())
133  call device_col2(w%x_d, coef%mult_d, w%dof%size())
134  else
135  call col2(u%x, coef%mult, u%dof%size())
136  call col2(v%x, coef%mult, v%dof%size())
137  call col2(w%x, coef%mult, w%dof%size())
138  end if
139 
140  end subroutine set_flow_ic_common
141 
143  subroutine set_flow_ic_uniform(u, v, w, uinf)
144  type(field_t), intent(inout) :: u
145  type(field_t), intent(inout) :: v
146  type(field_t), intent(inout) :: w
147  real(kind=rp), intent(in) :: uinf(3)
148  integer :: n
149  u = uinf(1)
150  v = uinf(2)
151  w = uinf(3)
152  n = u%dof%size()
153  if (neko_bcknd_device .eq. 1) then
154  call cfill(u%x, uinf(1), n)
155  call cfill(v%x, uinf(2), n)
156  call cfill(w%x, uinf(3), n)
157  end if
158 
159  end subroutine set_flow_ic_uniform
160 
163  subroutine set_flow_ic_blasius(u, v, w, delta, uinf, type)
164  type(field_t), intent(inout) :: u
165  type(field_t), intent(inout) :: v
166  type(field_t), intent(inout) :: w
167  real(kind=rp), intent(in) :: delta
168  real(kind=rp), intent(in) :: uinf(3)
169  character(len=*), intent(in) :: type
170  procedure(blasius_profile), pointer :: bla => null()
171  integer :: i
172 
173  select case(trim(type))
174  case('linear')
175  bla => blasius_linear
176  case('quadratic')
177  bla => blasius_quadratic
178  case('cubic')
179  bla => blasius_cubic
180  case('quartic')
181  bla => blasius_quartic
182  case('sin')
183  bla => blasius_sin
184  case default
185  call neko_error('Invalid Blasius approximation')
186  end select
187 
188  if ((uinf(1) .gt. 0.0_rp) .and. (uinf(2) .eq. 0.0_rp) &
189  .and. (uinf(3) .eq. 0.0_rp)) then
190  do i = 1, u%dof%size()
191  u%x(i,1,1,1) = bla(u%dof%z(i,1,1,1), delta, uinf(1))
192  v%x(i,1,1,1) = 0.0_rp
193  w%x(i,1,1,1) = 0.0_rp
194  end do
195  else if ((uinf(1) .eq. 0.0_rp) .and. (uinf(2) .gt. 0.0_rp) &
196  .and. (uinf(3) .eq. 0.0_rp)) then
197  do i = 1, u%dof%size()
198  u%x(i,1,1,1) = 0.0_rp
199  v%x(i,1,1,1) = bla(u%dof%x(i,1,1,1), delta, uinf(2))
200  w%x(i,1,1,1) = 0.0_rp
201  end do
202  else if ((uinf(1) .eq. 0.0_rp) .and. (uinf(2) .eq. 0.0_rp) &
203  .and. (uinf(3) .gt. 0.0_rp)) then
204  do i = 1, u%dof%size()
205  u%x(i,1,1,1) = 0.0_rp
206  v%x(i,1,1,1) = 0.0_rp
207  w%x(i,1,1,1) = bla(u%dof%y(i,1,1,1), delta, uinf(3))
208  end do
209  end if
210 
211  end subroutine set_flow_ic_blasius
212 
213 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:53
Coefficients.
Definition: coef.f90:34
subroutine, public device_col2(a_d, b_d, n)
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:93
subroutine set_flow_ic_int(u, v, w, p, coef, gs, type, params)
Set initial flow condition (builtin)
Definition: flow_ic.f90:60
subroutine set_flow_ic_uniform(u, v, w, uinf)
Uniform initial condition.
Definition: flow_ic.f90:144
subroutine set_flow_ic_common(u, v, w, p, coef, gs)
Definition: flow_ic.f90:109
subroutine set_flow_ic_blasius(u, v, w, delta, uinf, type)
Set a Blasius profile as initial condition.
Definition: flow_ic.f90:164
Defines a flow profile.
real(kind=rp) function blasius_quadratic(y, delta, u)
Quadratic approximate Blasius Profile .
real(kind=rp) function blasius_sin(y, delta, u)
Sinusoidal approximate Blasius Profile .
real(kind=rp) function blasius_cubic(y, delta, u)
Cubic approximate Blasius Profile .
real(kind=rp) function blasius_linear(y, delta, u)
Linear approximate Blasius profile .
real(kind=rp) function blasius_quartic(y, delta, u)
Quartic 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:270
subroutine, public col2(a, b, n)
Vector multiplication .
Definition: math.f90:645
Build configurations.
Definition: neko_config.f90:34
integer, parameter neko_bcknd_device
Definition: neko_config.f90:44
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:54