Neko  0.8.99
A portable framework for high-order spectral element flow simulations
point_zone.f90
Go to the documentation of this file.
1 ! Copyright (c) 2019-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 ! Implements a zone as a subset of GLL points in the mesh
34 module point_zone
35  use stack, only: stack_i4_t
36  use num_types, only: rp
37  use utils, only: neko_error, nonlinear_index
38  use dofmap, only: dofmap_t
39  use json_module, only: json_file
41  use device
42  use, intrinsic :: iso_c_binding, only: c_ptr, c_null_ptr
43  implicit none
44  private
45 
47  type, public, abstract :: point_zone_t
49  integer, allocatable :: mask(:)
51  type(c_ptr) :: mask_d = c_null_ptr
53  type(stack_i4_t), private :: scratch
55  integer :: size = 0
58  logical, private :: finalized = .false.
60  character(len=80) :: name
62  logical :: invert = .false.
63  contains
65  procedure, pass(this) :: init_base => point_zone_init_base
67  procedure, pass(this) :: free_base => point_zone_free_base
69  procedure, pass(this) :: finalize => point_zone_finalize
71  procedure, pass(this) :: add => point_zone_add
74  procedure, pass(this) :: map => point_zone_map
76  procedure(point_zone_init), pass(this), deferred :: init
78  procedure(point_zone_free), pass(this), deferred :: free
80  procedure(point_zone_criterion), pass(this), deferred :: criterion
81  end type point_zone_t
82 
84  type, public :: point_zone_wrapper_t
85  class(point_zone_t), allocatable :: pz
86  end type point_zone_wrapper_t
87 
89  type, public :: point_zone_pointer_t
90  class(point_zone_t), pointer :: pz => null()
91  end type point_zone_pointer_t
92 
93  abstract interface
94 
102  pure function point_zone_criterion(this, x, y, z, j, k, l, e) &
103  result(is_inside)
104  import :: point_zone_t
105  import :: rp
106  class(point_zone_t), intent(in) :: this
107  real(kind=rp), intent(in) :: x
108  real(kind=rp), intent(in) :: y
109  real(kind=rp), intent(in) :: z
110  integer, intent(in) :: j
111  integer, intent(in) :: k
112  integer, intent(in) :: l
113  integer, intent(in) :: e
114  logical :: is_inside
115  end function point_zone_criterion
116  end interface
117 
118  abstract interface
119 
122  subroutine point_zone_init(this, json, size)
123  import :: point_zone_t
124  import :: json_file
125  import :: dofmap_t
126  class(point_zone_t), intent(inout) :: this
127  type(json_file), intent(inout) :: json
128  integer, intent(in) :: size
129  end subroutine point_zone_init
130  end interface
131 
132  abstract interface
133 
134  subroutine point_zone_free(this)
135  import :: point_zone_t
136  class(point_zone_t), intent(inout) :: this
137  end subroutine point_zone_free
138  end interface
139 
140  interface
141 
146  module subroutine point_zone_factory(object, json, dof)
147  class(point_zone_t), allocatable, intent(inout) :: object
148  type(json_file), intent(inout) :: json
149  type(dofmap_t), intent(inout), optional :: dof
150  end subroutine point_zone_factory
151  end interface
152 
153  public :: point_zone_factory
154 
155 contains
156 
162  subroutine point_zone_init_base(this, size, name, invert)
163  class(point_zone_t), intent(inout) :: this
164  integer, intent(in), optional :: size
165  character(len=*), intent(in) :: name
166  logical, intent(in) :: invert
167 
168  call point_zone_free_base(this)
169 
170  if (present(size)) then
171  call this%scratch%init(size)
172  else
173  call this%scratch%init()
174  end if
175 
176  this%name = trim(name)
177  this%invert = invert
178 
179  end subroutine point_zone_init_base
180 
182  subroutine point_zone_free_base(this)
183  class(point_zone_t), intent(inout) :: this
184  if (allocated(this%mask)) then
185  deallocate(this%mask)
186  end if
187 
188  this%finalized = .false.
189  this%size = 0
190 
191  call this%scratch%free()
192 
193  if (c_associated(this%mask_d)) then
194  call device_free(this%mask_d)
195  end if
196 
197  end subroutine point_zone_free_base
198 
200  subroutine point_zone_finalize(this)
201  class(point_zone_t), intent(inout) :: this
202  integer, pointer :: tp(:)
203  integer :: i
204 
205  if (.not. this%finalized) then
206 
207  if (this%scratch%size() .ne. 0) then
208 
209  allocate(this%mask(this%scratch%size()))
210 
211  tp => this%scratch%array()
212  do i = 1, this%scratch%size()
213  this%mask(i) = tp(i)
214  end do
215 
216  this%size = this%scratch%size()
217 
218  call this%scratch%clear()
219 
220  if (neko_bcknd_device .eq. 1) then
221  call device_map(this%mask, this%mask_d, this%size)
222  call device_memcpy(this%mask, this%mask_d, this%size, &
223  host_to_device, sync = .false.)
224  end if
225 
226  else
227 
228  this%size = 0
229  call this%scratch%clear()
230 
231  end if
232 
233  this%finalized = .true.
234 
235  end if
236 
237  end subroutine point_zone_finalize
238 
243  subroutine point_zone_add(this, idx)
244  class(point_zone_t), intent(inout) :: this
245  integer, intent(inout) :: idx
246 
247  if (this%finalized) then
248  call neko_error('Point zone already finalized')
249  end if
250 
251  call this%scratch%push(idx)
252 
253  end subroutine point_zone_add
254 
258  subroutine point_zone_map(this, dof)
259  class(point_zone_t), intent(inout) :: this
260  type(dofmap_t), intent(in) :: dof
261 
262  integer :: i, ix, iy, iz, ie, nlindex(4), lx, idx
263  real(kind=rp) :: x, y, z
264 
265  lx = dof%Xh%lx
266 
267  do i = 1, dof%size()
268  nlindex = nonlinear_index(i, lx, lx, lx)
269  x = dof%x(nlindex(1), nlindex(2), nlindex(3), nlindex(4))
270  y = dof%y(nlindex(1), nlindex(2), nlindex(3), nlindex(4))
271  z = dof%z(nlindex(1), nlindex(2), nlindex(3), nlindex(4))
272  ix = nlindex(1)
273  iy = nlindex(2)
274  iz = nlindex(3)
275  ie = nlindex(4)
276 
277  if (this%invert .neqv. this%criterion(x, y, z, ix, iy, iz, ie)) then
278  idx = i
279  call this%add(idx)
280  end if
281  end do
282 
283  end subroutine point_zone_map
284 
285 end module point_zone
__device__ void nonlinear_index(const int idx, const int lx, int *index)
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
Defines the criterion of selection of a GLL point to the point_zone.
Definition: point_zone.f90:102
The common constructor using a JSON object.
Definition: point_zone.f90:122
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
Defines a mapping of the degrees of freedom.
Definition: dofmap.f90:35
NEKTON map.
Definition: map.f90:3
Build configurations.
Definition: neko_config.f90:34
integer, parameter neko_bcknd_device
Definition: neko_config.f90:44
integer, parameter, public rp
Global precision used in computations.
Definition: num_types.f90:12
subroutine point_zone_free_base(this)
Destructor for the point_zone_t base type.
Definition: point_zone.f90:183
subroutine point_zone_add(this, idx)
Adds a point's linear index to the scratch stack.
Definition: point_zone.f90:244
subroutine point_zone_finalize(this)
Builds the mask from the scratch stack.
Definition: point_zone.f90:201
subroutine point_zone_init_base(this, size, name, invert)
Point zone factory. Constructs, initializes, and maps the point zone object.
Definition: point_zone.f90:163
subroutine point_zone_map(this, dof)
Maps the GLL points that verify a point_zone's criterion by adding them to the stack.
Definition: point_zone.f90:259
Implements a dynamic stack ADT.
Definition: stack.f90:35
Utilities.
Definition: utils.f90:35
A helper type to build a list of pointers to point_zones.
Definition: point_zone.f90:89
Base abstract type for point zones.
Definition: point_zone.f90:47
A helper type to build a list of polymorphic point_zones.
Definition: point_zone.f90:84
Integer based stack.
Definition: stack.f90:63