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
elementwise_filter.f90
Go to the documentation of this file.
1! Copyright (c) 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!
33!
36 use num_types, only : rp
37 use filter, only: filter_t
38 use math, only : rzero, rone, copy
39 use field, only : field_t
40 use coefs, only : coef_t
41 use utils, only : neko_error
43 use json_module, only : json_file
45 use speclib, only : zwgll, legendre_poly
46 use matrix, only : matrix_t
47 use mxm_wrapper, only : mxm
48 use tensor, only : tnsr3d, trsp
50 use device_math, only : device_cfill
51 use, intrinsic :: iso_c_binding, only : c_ptr, c_null_ptr, c_associated
52 implicit none
53 private
54
56 type, public, extends(filter_t) :: elementwise_filter_t
59 character(len=:), allocatable :: filter_type
61 integer :: nx
63 integer :: nt
65 real(kind=rp), allocatable :: fh(:,:), fht(:,:)
66 type(c_ptr) :: fh_d = c_null_ptr
67 type(c_ptr) :: fht_d = c_null_ptr
69 real(kind=rp), allocatable :: trnsfr(:)
70 contains
72 procedure, pass(this) :: init => elementwise_filter_init_from_json
74 procedure, pass(this) :: init_from_components => &
77 procedure, pass(this) :: free => elementwise_filter_free
79 procedure, pass(this) :: build_1d
81 procedure, pass(this) :: apply => elementwise_field_filter_3d
83
84contains
86 subroutine elementwise_filter_init_from_json(this, json, coef)
87 class(elementwise_filter_t), intent(inout) :: this
88 type(json_file), intent(inout) :: json
89 type(coef_t), intent(in) :: coef
90 character(len=:), allocatable :: filter_type
91
92 call json_get_or_default(json, "test_filter_type", filter_type, "nonBoyd")
93 this%filter_type = filter_type
94
95 ! Filter assumes lx = ly = lz
96 call this%init_base(json, coef)
97
98 call this%init_from_components(coef%dof%xh%lx, this%filter_type)
99
104 subroutine elementwise_filter_init_from_components(this, nx, filter_type)
105 class(elementwise_filter_t), intent(inout) :: this
106 character(len=*) :: filter_type
107 integer :: nx
108
109 this%nx = nx
110 this%nt = nx ! initialize as if nothing is filtered yet
111
112 allocate(this%fh(nx, nx))
113 allocate(this%fht(nx, nx))
114 allocate(this%trnsfr(nx))
115
116 call rzero(this%fh, nx*nx)
117 call rzero(this%fht, nx*nx)
118 call rone(this%trnsfr, nx) ! initialize as if nothing is filtered yet
119
120 if (neko_bcknd_device .eq. 1) then
121 call device_map(this%fh, this%fh_d, this%nx * this%nx)
122 call device_map(this%fht, this%fht_d, this%nx * this%nx)
123 call device_cfill(this%fh_d, 0.0_rp, this%nx * this%nx)
124 call device_cfill(this%fht_d, 0.0_rp, this%nx * this%nx)
125 end if
126
128
130 subroutine elementwise_filter_free(this)
131 class(elementwise_filter_t), intent(inout) :: this
132
133 if (allocated(this%fh)) then
134 deallocate(this%fh)
135 end if
136
137 if (allocated(this%fht)) then
138 deallocate(this%fht)
139 end if
140
141 if (allocated(this%trnsfr)) then
142 deallocate(this%trnsfr)
143 end if
144
145 if (c_associated(this%fh_d)) then
146 call device_free(this%fh_d)
147 end if
148
149 if (c_associated(this%fht_d)) then
150 call device_free(this%fht_d)
151 end if
152
153 this%filter_type = ""
154 this%nx = 0
155 this%nt = 0
156
157 call this%free_base()
158
159 end subroutine elementwise_filter_free
160
162 subroutine build_1d(this)
163 class(elementwise_filter_t), intent(inout) :: this
164
165 call build_1d_cpu(this%fh, this%fht, this%trnsfr, &
166 this%nx, this%filter_type)
167 if (neko_bcknd_device .eq. 1) then
168 call device_memcpy(this%fh, this%fh_d, &
169 this%nx * this%nx, host_to_device, sync = .false.)
170 call device_memcpy(this%fht, this%fht_d, &
171 this%nx * this%nx, host_to_device, sync = .false.)
172 end if
173
174 end subroutine build_1d
175
177 subroutine elementwise_field_filter_3d(this, F_out, F_in)
178 class(elementwise_filter_t), intent(inout) :: this
179 type(field_t), intent(inout) :: F_out
180 type(field_t), intent(in) :: F_in
181
182 ! F_out = fh x fh x fh x F_in
183 call tnsr3d(f_out%x, this%nx, f_in%x, this%nx, this%fh, this%fht, this%fht, &
184 this%coef%msh%nelv)
185
186 end subroutine elementwise_field_filter_3d
187
195 subroutine build_1d_cpu(fh, fht, trnsfr, nx, filter_type)
196 integer, intent(in) :: nx
197 real(kind=rp), intent(inout) :: fh(nx, nx), fht(nx, nx)
198 real(kind=rp), intent(in) :: trnsfr(nx)
199 real(kind=rp) :: diag(nx, nx), rmult(nx), lj(nx), zpts(nx)
200 type(matrix_t) :: phi, pht
201 integer :: n, i, j, k
202 real(kind=rp) :: z
203 character(len=*), intent(in) :: filter_type
204
205 call phi%init(nx, nx)
206 call pht%init(nx, nx)
207
208 call zwgll(zpts, rmult, nx)
209
210 n = nx-1
211 do j = 1, nx
212 z = zpts(j)
213 call legendre_poly(lj, z, n)
214 select case (filter_type)
215 case("Boyd")
216 pht%x(1,j) = lj(1)
217 pht%x(2,j) = lj(2)
218 do k=3,nx
219 pht%x(k,j) = lj(k)-lj(k-2)
220 end do
221 case("nonBoyd")
222 pht%x(:,j) = lj
223 end select
224 end do
225
226 call trsp(phi%x, nx, pht%x, nx)
227 pht%x = phi%x
228
229 call pht%inverse(0) ! "0" for cpu implementation
230
231 diag = 0.0_rp
232
233 do i=1,nx
234 diag(i,i) = trnsfr(i)
235 end do
236
237 call mxm (diag, nx, pht%x, nx, fh, nx) ! -1
238 call mxm (phi%x, nx, fh, nx, pht%x, nx) ! V D V
239
240 call copy (fh, pht%x, nx*nx)
241 call trsp (fht, nx, fh, nx)
242
243 end subroutine build_1d_cpu
244
245end module elementwise_filter
Map a Fortran array to a device (allocate and associate)
Definition device.F90:71
Copy data between host and device (or device and device)
Definition device.F90:65
Retrieves a parameter by name or assigns a provided default value. In the latter case also adds the m...
Coefficients.
Definition coef.f90:34
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:46
subroutine, public device_free(x_d)
Deallocate memory on the device.
Definition device.F90:200
Implements explicit_filter_t.
subroutine build_1d_cpu(fh, fht, trnsfr, nx, filter_type)
Build the 1d filter for an element on the CPU. Suppose field x is filtered into x_hat by x_hat = fh*x...
subroutine elementwise_filter_init_from_json(this, json, coef)
Constructor.
subroutine elementwise_filter_free(this)
Destructor.
subroutine build_1d(this)
Build the 1d filter for an element.
subroutine elementwise_filter_init_from_components(this, nx, filter_type)
Actual Constructor.
subroutine elementwise_field_filter_3d(this, f_out, f_in)
Filter a 3D field.
Defines a field.
Definition field.f90:34
Filter to be applied to a scalar field.
Definition filter.f90:38
Utilities for retrieving parameters from the case files.
Definition math.f90:60
subroutine, public rone(a, n)
Set all elements to one.
Definition math.f90:227
subroutine, public copy(a, b, n)
Copy a vector .
Definition math.f90:238
subroutine, public rzero(a, n)
Zero a real vector.
Definition math.f90:194
Defines a matrix.
Definition matrix.f90:34
Wrapper for all matrix-matrix product implementations.
subroutine, public mxm(a, n1, b, n2, c, n3)
Compute matrix-matrix product for contiguously packed matrices A,B, and C.
Build configurations.
integer, parameter neko_bcknd_device
integer, parameter, public rp
Global precision used in computations.
Definition num_types.f90:12
LIBRARY ROUTINES FOR SPECTRAL METHODS.
Definition speclib.f90:148
subroutine zwgll(z, w, np)
Definition speclib.f90:169
subroutine legendre_poly(l, x, n)
Evaluate Legendre polynomials of degrees 0-N at point x and store in array L.
Definition speclib.f90:980
Tensor operations.
Definition tensor.f90:61
subroutine, public trsp(a, lda, b, ldb)
Transpose of a rectangular tensor .
Definition tensor.f90:121
subroutine, public tnsr3d(v, nv, u, nu, a, bt, ct, nelv)
Tensor product performed on nelv elements.
Definition tensor.f90:223
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
Implements the explicit filter for SEM.
Base abstract class for filter.
Definition filter.f90:48