Neko 0.9.99
A portable framework for high-order spectral element flow simulations
Loading...
Searching...
No Matches
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 math, only : rzero, rone
38 use field, only : field_t
39 use utils, only : neko_error
42 use tensor, only : tnsr3d
43 use device, only : device_map, device_free, c_ptr, &
44 c_null_ptr, device_memcpy, host_to_device
45 use device_math, only : device_cfill
46 use, intrinsic :: iso_c_binding
47 implicit none
48 private
49
51 type, public :: elementwise_filter_t
54 character(len=64) :: filter_type
56 integer :: nx
58 integer :: nt
60 real(kind=rp), allocatable :: fh(:,:), fht(:,:)
61 type(c_ptr) :: fh_d = c_null_ptr
62 type(c_ptr) :: fht_d = c_null_ptr
64 real(kind=rp), allocatable :: trnsfr(:)
65 contains
67 procedure, pass(this) :: init => elementwise_filter_init
69 procedure, pass(this) :: free => elementwise_filter_free
71 procedure, pass(this) :: build_1d
73 procedure, pass(this) :: filter_3d => elementwise_field_filter_3d
75
76contains
80 subroutine elementwise_filter_init(this, nx, filter_type)
81 class(elementwise_filter_t), intent(inout) :: this
82 character(len=*) :: filter_type
83 integer :: nx
84
85 this%nx = nx
86 this%nt = nx ! initialize as if nothing is filtered yet
87 this%filter_type = filter_type
88
89 allocate(this%fh(nx, nx))
90 allocate(this%fht(nx, nx))
91 allocate(this%trnsfr(nx))
92
93 call rzero(this%fh, nx*nx)
94 call rzero(this%fht, nx*nx)
95 call rone(this%trnsfr, nx) ! initialize as if nothing is filtered yet
96
97 if (neko_bcknd_device .eq. 1) then
98 call device_map(this%fh, this%fh_d, this%nx * this%nx)
99 call device_map(this%fht, this%fht_d, this%nx * this%nx)
100 call device_cfill(this%fh_d, 0.0_rp, this%nx * this%nx)
101 call device_cfill(this%fht_d, 0.0_rp, this%nx * this%nx)
102 end if
103
104 end subroutine elementwise_filter_init
105
107 subroutine elementwise_filter_free(this)
108 class(elementwise_filter_t), intent(inout) :: this
109
110 if (allocated(this%fh)) then
111 deallocate(this%fh)
112 end if
113
114 if (allocated(this%fht)) then
115 deallocate(this%fht)
116 end if
117
118 if (allocated(this%trnsfr)) then
119 deallocate(this%trnsfr)
120 end if
121
122 if (c_associated(this%fh_d)) then
123 call device_free(this%fh_d)
124 end if
125
126 if (c_associated(this%fht_d)) then
127 call device_free(this%fht_d)
128 end if
129
130 this%filter_type = ""
131 this%nx = 0
132 this%nt = 0
133
134 end subroutine elementwise_filter_free
135
137 subroutine build_1d(this)
138 class(elementwise_filter_t), intent(inout) :: this
139
140 call build_1d_cpu(this%fh, this%fht, this%trnsfr, &
141 this%nx, this%filter_type)
142 if (neko_bcknd_device .eq. 1) then
143 call device_memcpy(this%fh, this%fh_d, &
144 this%nx * this%nx, host_to_device, sync = .false.)
145 call device_memcpy(this%fht, this%fht_d, &
146 this%nx * this%nx, host_to_device, sync = .false.)
147 end if
148
149 end subroutine build_1d
150
152 subroutine elementwise_field_filter_3d(this, v, u, nelv)
153 class(elementwise_filter_t), intent(in) :: this
154 integer, intent(inout) :: nelv
155 real(kind=rp), intent(inout), dimension(this%nx, this%nx, this%nx, nelv) :: v
156 real(kind=rp), intent(in), dimension(this%nx, this%nx, this%nx, nelv) :: u
157
158 ! v = fh x fh x fh x u
159 call tnsr3d(v, this%nx, u, this%nx, this%fh, this%fht, this%fht, nelv)
160
161 end subroutine elementwise_field_filter_3d
162
163end module elementwise_filter
Map a Fortran array to a device (allocate and associate)
Definition device.F90:57
Copy data between host and device (or device and device)
Definition device.F90:51
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
subroutine, public device_free(x_d)
Deallocate memory on the device.
Definition device.F90:185
Implements the CPU kernel for the elementwise_filter_t type.
subroutine, public 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...
Implements explicit_filter_t.
subroutine elementwise_field_filter_3d(this, v, u, nelv)
Filter a 3D field.
subroutine elementwise_filter_free(this)
Destructor.
subroutine build_1d(this)
Build the 1d filter for an element.
subroutine elementwise_filter_init(this, nx, filter_type)
Constructor.
Defines a field.
Definition field.f90:34
Definition math.f90:60
subroutine, public rone(a, n)
Set all elements to one.
Definition math.f90:227
subroutine, public rzero(a, n)
Zero a real vector.
Definition math.f90:194
Build configurations.
integer, parameter neko_bcknd_device
integer, parameter, public rp
Global precision used in computations.
Definition num_types.f90:12
Tensor operations.
Definition tensor.f90:61
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
Implements the explicit filter for SEM.