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
zero_dirichlet.f90
Go to the documentation of this file.
1! Copyright (c) 2020-2024, 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!
36 use num_types, only : rp
37 use bc, only : bc_t
38 use, intrinsic :: iso_c_binding, only : c_ptr
39 use coefs, only : coef_t
40 use json_module, only : json_file
41 implicit none
42 private
43
47 type, public, extends(bc_t) :: zero_dirichlet_t
48 contains
49 procedure, pass(this) :: apply_scalar => zero_dirichlet_apply_scalar
50 procedure, pass(this) :: apply_vector => zero_dirichlet_apply_vector
51 procedure, pass(this) :: apply_scalar_dev => &
53 procedure, pass(this) :: apply_vector_dev => &
56 procedure, pass(this) :: init => zero_dirichlet_init
58 procedure, pass(this) :: init_from_components => &
61 procedure, pass(this) :: free => zero_dirichlet_free
63 procedure, pass(this) :: finalize => zero_dirichlet_finalize
64 end type zero_dirichlet_t
65
66contains
67
71 subroutine zero_dirichlet_init(this, coef, json)
72 class(zero_dirichlet_t), intent(inout), target :: this
73 type(coef_t), intent(in) :: coef
74 type(json_file), intent(inout) :: json
75
76 call this%init_from_components(coef)
77 end subroutine zero_dirichlet_init
78
82 class(zero_dirichlet_t), intent(inout), target :: this
83 type(coef_t), intent(in) :: coef
84
85 call this%init_base(coef)
87
90 subroutine zero_dirichlet_apply_scalar(this, x, n, t, tstep, strong)
91 class(zero_dirichlet_t), intent(inout) :: this
92 integer, intent(in) :: n
93 real(kind=rp), intent(inout), dimension(n) :: x
94 real(kind=rp), intent(in), optional :: t
95 integer, intent(in), optional :: tstep
96 logical, intent(in), optional :: strong
97 integer :: i, m, k
98 logical :: strong_ = .true.
99
100 if (present(strong)) strong_ = strong
101 m = this%msk(0)
102
103 if (strong_) then
104 do i = 1, m
105 k = this%msk(i)
106 x(k) = 0d0
107 end do
108 end if
109
110 end subroutine zero_dirichlet_apply_scalar
111
113 subroutine zero_dirichlet_apply_vector(this, x, y, z, n, t, tstep, strong)
114 class(zero_dirichlet_t), intent(inout) :: this
115 integer, intent(in) :: n
116 real(kind=rp), intent(inout), dimension(n) :: x
117 real(kind=rp), intent(inout), dimension(n) :: y
118 real(kind=rp), intent(inout), dimension(n) :: z
119 real(kind=rp), intent(in), optional :: t
120 integer, intent(in), optional :: tstep
121 logical, intent(in), optional :: strong
122 integer :: i, m, k
123 logical :: strong_ = .true.
124
125 if (present(strong)) strong_ = strong
126
127 if (strong_) then
128 m = this%msk(0)
129 do i = 1, m
130 k = this%msk(i)
131 x(k) = 0d0
132 y(k) = 0d0
133 z(k) = 0d0
134 end do
135 end if
136
137 end subroutine zero_dirichlet_apply_vector
138
140 subroutine zero_dirichlet_apply_scalar_dev(this, x_d, t, tstep, strong)
141 class(zero_dirichlet_t), intent(inout), target :: this
142 type(c_ptr) :: x_d
143 real(kind=rp), intent(in), optional :: t
144 integer, intent(in), optional :: tstep
145 logical, intent(in), optional :: strong
146 logical :: strong_ = .true.
147
148 if (present(strong)) strong_ = strong
149
150 if (strong_ .and. (this%msk(0) .gt. 0)) then
151 call device_zero_dirichlet_apply_scalar(this%msk_d, x_d, size(this%msk))
152 end if
153
155
157 subroutine zero_dirichlet_apply_vector_dev(this, x_d, y_d, z_d, t, tstep, &
158 strong)
159 class(zero_dirichlet_t), intent(inout), target :: this
160 type(c_ptr) :: x_d
161 type(c_ptr) :: y_d
162 type(c_ptr) :: z_d
163 real(kind=rp), intent(in), optional :: t
164 integer, intent(in), optional :: tstep
165 logical, intent(in), optional :: strong
166 logical :: strong_ = .true.
167
168 if (present(strong)) strong_ = strong
169
170 if (strong_ .and. (this%msk(0) .gt. 0)) then
171 call device_zero_dirichlet_apply_vector(this%msk_d, x_d, y_d, z_d, &
172 size(this%msk))
173 end if
174
176
178 subroutine zero_dirichlet_free(this)
179 class(zero_dirichlet_t), target, intent(inout) :: this
180
181 call this%free_base()
182
183 end subroutine zero_dirichlet_free
184
186 subroutine zero_dirichlet_finalize(this)
187 class(zero_dirichlet_t), target, intent(inout) :: this
188
189 call this%finalize_base()
190 end subroutine zero_dirichlet_finalize
191
192end module zero_dirichlet
Defines a boundary condition.
Definition bc.f90:34
Coefficients.
Definition coef.f90:34
subroutine, public device_zero_dirichlet_apply_scalar(msk, x, m)
subroutine, public device_zero_dirichlet_apply_vector(msk, x, y, z, m)
integer, parameter, public rp
Global precision used in computations.
Definition num_types.f90:12
Defines a zero-valued Dirichlet boundary condition.
subroutine zero_dirichlet_apply_scalar(this, x, n, t, tstep, strong)
Apply boundary condition to a scalar field. to a vector x.
subroutine zero_dirichlet_init(this, coef, json)
Constructor.
subroutine zero_dirichlet_apply_vector(this, x, y, z, n, t, tstep, strong)
Apply boundary condition to a vector field.
subroutine zero_dirichlet_apply_scalar_dev(this, x_d, t, tstep, strong)
Apply boundary condition to a scalar field, device version.
subroutine zero_dirichlet_free(this)
Destructor.
subroutine zero_dirichlet_init_from_components(this, coef)
Constructor.
subroutine zero_dirichlet_finalize(this)
Finalize.
subroutine zero_dirichlet_apply_vector_dev(this, x_d, y_d, z_d, t, tstep, strong)
Apply boundary condition to a vector field, device version.
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
Zero-valued Dirichlet boundary condition. Used for no-slip walls, but also for various auxillary cond...