Neko  0.8.1
A portable framework for high-order spectral element flow simulations
point_zone.f90
Go to the documentation of this file.
1 ! Copyright (c) 2019-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 !
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
61  contains
63  procedure, pass(this) :: init_base => point_zone_init_base
65  procedure, pass(this) :: free_base => point_zone_free_base
67  procedure, pass(this) :: finalize => point_zone_finalize
69  procedure, pass(this) :: add => point_zone_add
72  procedure, pass(this) :: map => point_zone_map
74  procedure(point_zone_init), pass(this), deferred :: init
76  procedure(point_zone_free), pass(this), deferred :: free
78  procedure(point_zone_criterion), pass(this), deferred :: criterion
79  end type point_zone_t
80 
82  type, public :: point_zone_wrapper_t
83  class(point_zone_t), allocatable :: pz
84  end type point_zone_wrapper_t
85 
86  abstract interface
87 
95  pure function point_zone_criterion(this, x, y, z, j, k, l, e) result(is_inside)
96  import :: point_zone_t
97  import :: rp
98  class(point_zone_t), intent(in) :: this
99  real(kind=rp), intent(in) :: x
100  real(kind=rp), intent(in) :: y
101  real(kind=rp), intent(in) :: z
102  integer, intent(in) :: j
103  integer, intent(in) :: k
104  integer, intent(in) :: l
105  integer, intent(in) :: e
106  logical :: is_inside
107  end function point_zone_criterion
108  end interface
109 
110  abstract interface
111 
114  subroutine point_zone_init(this, json, size)
115  import :: point_zone_t
116  import :: json_file
117  import :: dofmap_t
118  class(point_zone_t), intent(inout) :: this
119  type(json_file), intent(inout) :: json
120  integer, intent(in) :: size
121  end subroutine point_zone_init
122  end interface
123 
124  abstract interface
125 
126  subroutine point_zone_free(this)
127  import :: point_zone_t
128  class(point_zone_t), intent(inout) :: this
129  end subroutine point_zone_free
130  end interface
131 
132 contains
133 
137  subroutine point_zone_init_base(this, size, name)
138  class(point_zone_t), intent(inout) :: this
139  integer, intent(in), optional :: size
140  character(len=*), intent(in) :: name
141 
142  call point_zone_free_base(this)
143 
144  if (present(size)) then
145  call this%scratch%init(size)
146  else
147  call this%scratch%init()
148  end if
149 
150  this%name = trim(name)
151 
152  end subroutine point_zone_init_base
153 
155  subroutine point_zone_free_base(this)
156  class(point_zone_t), intent(inout) :: this
157  if (allocated(this%mask)) then
158  deallocate(this%mask)
159  end if
160 
161  this%finalized = .false.
162  this%size = 0
163 
164  call this%scratch%free()
165 
166  if (c_associated(this%mask_d)) then
167  call device_free(this%mask_d)
168  end if
169 
170  end subroutine point_zone_free_base
171 
173  subroutine point_zone_finalize(this)
174  class(point_zone_t), intent(inout) :: this
175  integer, pointer :: tp(:)
176  integer :: i
177 
178  if (.not. this%finalized) then
179 
180  allocate(this%mask(this%scratch%size()))
181 
182  tp => this%scratch%array()
183  do i = 1, this%scratch%size()
184  this%mask(i) = tp(i)
185  end do
186 
187  this%size = this%scratch%size()
188 
189  call this%scratch%clear()
190 
191  if (neko_bcknd_device .eq. 1) then
192  call device_map(this%mask, this%mask_d, this%size)
193  call device_memcpy(this%mask, this%mask_d, this%size, &
194  host_to_device, sync=.false.)
195  end if
196 
197  this%finalized = .true.
198 
199  end if
200 
201  end subroutine point_zone_finalize
202 
207  subroutine point_zone_add(this, idx)
208  class(point_zone_t), intent(inout) :: this
209  integer, intent(inout) :: idx
210 
211  if (this%finalized) then
212  call neko_error('Point zone already finalized')
213  end if
214 
215  call this%scratch%push(idx)
216 
217  end subroutine point_zone_add
218 
222  subroutine point_zone_map(this, dof)
223  class(point_zone_t), intent(inout) :: this
224  type(dofmap_t), intent(in) :: dof
225 
226  integer :: i, ix, iy, iz, ie, nlindex(4), lx, idx
227  real(kind=rp) :: x, y, z
228 
229  lx = dof%Xh%lx
230 
231  do i = 1, dof%size()
232  nlindex = nonlinear_index(i, lx, lx, lx)
233  x = dof%x(nlindex(1), nlindex(2), nlindex(3), nlindex(4))
234  y = dof%y(nlindex(1), nlindex(2), nlindex(3), nlindex(4))
235  z = dof%z(nlindex(1), nlindex(2), nlindex(3), nlindex(4))
236  ix = nlindex(1)
237  iy = nlindex(2)
238  iz = nlindex(3)
239  ie = nlindex(4)
240 
241  if (this%criterion(x, y, z, ix, iy, iz, ie)) then
242  idx = i
243  call this%add(idx)
244  end if
245  end do
246 
247  end subroutine point_zone_map
248 
249 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:95
The common constructor using a JSON object.
Definition: point_zone.f90:114
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:172
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:156
subroutine point_zone_init_base(this, size, name)
Constructor for the point_zone_t base type.
Definition: point_zone.f90:138
subroutine point_zone_add(this, idx)
Adds a point's linear index to the scratch stack.
Definition: point_zone.f90:208
subroutine point_zone_finalize(this)
Builds the mask from the scratch stack.
Definition: point_zone.f90:174
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:223
Implements a dynamic stack ADT.
Definition: stack.f90:35
Utilities.
Definition: utils.f90:35
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:82
Integer based stack.
Definition: stack.f90:63