Loading [MathJax]/extensions/tex2jax.js
Neko 0.9.99
A portable framework for high-order spectral element flow simulations
All Classes Namespaces Files Functions Variables Typedefs Enumerator Macros Pages
inflow.f90
Go to the documentation of this file.
1! Copyright (c) 2020-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 inflow
36 use num_types, only : rp
37 use bc, only : bc_t
38 use, intrinsic :: iso_c_binding, only : c_ptr, c_loc
39 use coefs, only : coef_t
40 use json_module, only : json_file
41 use json_utils, only : json_get
42 implicit none
43 private
44
46 type, public, extends(bc_t) :: inflow_t
47 real(kind=rp), dimension(3) :: x = [0d0, 0d0, 0d0]
48 contains
49 procedure, pass(this) :: apply_scalar => inflow_apply_scalar
50 procedure, pass(this) :: apply_vector => inflow_apply_vector
51 procedure, pass(this) :: apply_scalar_dev => inflow_apply_scalar_dev
52 procedure, pass(this) :: apply_vector_dev => inflow_apply_vector_dev
54 procedure, pass(this) :: init => inflow_init
56 procedure, pass(this) :: free => inflow_free
58 procedure, pass(this) :: finalize => inflow_finalize
59 end type inflow_t
60
61contains
62
66 subroutine inflow_init(this, coef, json)
67 class(inflow_t), intent(inout), target :: this
68 type(coef_t), intent(in) :: coef
69 type(json_file), intent(inout) ::json
70 real(kind=rp), allocatable :: x(:)
71
72 call this%init_base(coef)
73 call json_get(json, 'value', x)
74 this%x = x
75 end subroutine inflow_init
76
78 subroutine inflow_apply_scalar(this, x, n, t, tstep, strong)
79 class(inflow_t), intent(inout) :: this
80 integer, intent(in) :: n
81 real(kind=rp), intent(inout), dimension(n) :: x
82 real(kind=rp), intent(in), optional :: t
83 integer, intent(in), optional :: tstep
84 logical, intent(in), optional :: strong
85 end subroutine inflow_apply_scalar
86
88 subroutine inflow_apply_scalar_dev(this, x_d, t, tstep, strong)
89 class(inflow_t), intent(inout), target :: this
90 type(c_ptr) :: x_d
91 real(kind=rp), intent(in), optional :: t
92 integer, intent(in), optional :: tstep
93 logical, intent(in), optional :: strong
94 end subroutine inflow_apply_scalar_dev
95
97 subroutine inflow_apply_vector(this, x, y, z, n, t, tstep, strong)
98 class(inflow_t), intent(inout) :: this
99 integer, intent(in) :: n
100 real(kind=rp), intent(inout), dimension(n) :: x
101 real(kind=rp), intent(inout), dimension(n) :: y
102 real(kind=rp), intent(inout), dimension(n) :: z
103 real(kind=rp), intent(in), optional :: t
104 logical, intent(in), optional :: strong
105 integer, intent(in), optional :: tstep
106 integer :: i, m, k
107 logical :: strong_ = .true.
108
109 if (present(strong)) strong_ = strong
110
111 m = this%msk(0)
112
113 if (strong_) then
114 do i = 1, m
115 k = this%msk(i)
116 x(k) = this%x(1)
117 y(k) = this%x(2)
118 z(k) = this%x(3)
119 end do
120 end if
121 end subroutine inflow_apply_vector
122
124 subroutine inflow_apply_vector_dev(this, x_d, y_d, z_d, t, tstep, strong)
125 class(inflow_t), intent(inout), target :: this
126 type(c_ptr) :: x_d
127 type(c_ptr) :: y_d
128 type(c_ptr) :: z_d
129 real(kind=rp), intent(in), optional :: t
130 integer, intent(in), optional :: tstep
131 logical, intent(in), optional :: strong
132 logical :: strong_ = .true.
133
134 if (present(strong)) strong_ = strong
135
136 if (strong_ .and. (this%msk(0) .gt. 0)) then
137 call device_inflow_apply_vector(this%msk_d, x_d, y_d, z_d, &
138 c_loc(this%x), this%msk(0))
139 end if
140
141 end subroutine inflow_apply_vector_dev
142
144 subroutine inflow_free(this)
145 class(inflow_t), target, intent(inout) :: this
146
147 call this%free_base()
148 end subroutine inflow_free
149
151 subroutine inflow_finalize(this)
152 class(inflow_t), target, intent(inout) :: this
153
154 call this%finalize_base()
155 end subroutine inflow_finalize
156
157
158end module inflow
Retrieves a parameter by name or throws an error.
Defines a boundary condition.
Definition bc.f90:34
Coefficients.
Definition coef.f90:34
subroutine, public device_inflow_apply_vector(msk, x, y, z, g, m)
Defines inflow dirichlet conditions.
Definition inflow.f90:34
subroutine inflow_apply_scalar_dev(this, x_d, t, tstep, strong)
No-op scalar apply (device version)
Definition inflow.f90:89
subroutine inflow_apply_vector(this, x, y, z, n, t, tstep, strong)
Apply inflow conditions (vector valued)
Definition inflow.f90:98
subroutine inflow_finalize(this)
Finalize.
Definition inflow.f90:152
subroutine inflow_init(this, coef, json)
Constructor.
Definition inflow.f90:67
subroutine inflow_apply_vector_dev(this, x_d, y_d, z_d, t, tstep, strong)
Apply inflow conditions (vector valued) (device version)
Definition inflow.f90:125
subroutine inflow_apply_scalar(this, x, n, t, tstep, strong)
No-op scalar apply.
Definition inflow.f90:79
subroutine inflow_free(this)
Destructor.
Definition inflow.f90:145
Utilities for retrieving parameters from the case files.
integer, parameter, public rp
Global precision used in computations.
Definition num_types.f90:12
Base type for a boundary condition.
Definition bc.f90:57
Coefficients defined on a given (mesh, ) tuple. Arrays use indices (i,j,k,e): element e,...
Definition coef.f90:55
Dirichlet condition for inlet (vector valued)
Definition inflow.f90:46