Neko  0.8.99
A portable framework for high-order spectral element flow simulations
combine_point_zone.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 ! Implements a geometry subset that combines different zones.
36  point_zone_wrapper_t, point_zone_factory
40  use num_types, only : rp
42  use json_module, only : json_file, json_core, json_value
44  use logger, only : neko_log
45  implicit none
46  private
47 
49  type, public, extends(point_zone_t) :: combine_point_zone_t
51  type(point_zone_pointer_t), allocatable :: zones(:)
53  type(point_zone_wrapper_t), allocatable :: internal_zones(:)
55  character(len=80), allocatable :: names(:)
57  integer :: n_zones = 0
59  integer :: n_external_zones = 0
61  integer :: n_internal_zones = 0
62 
64  character(len=:), allocatable :: operator
65  contains
67  procedure, pass(this) :: init => combine_point_zone_init_from_json
69  procedure, pass(this) :: free => combine_point_zone_free
72  procedure, pass(this) :: criterion => combine_point_zone_criterion
73  end type combine_point_zone_t
74 
75 contains
76 
80  subroutine combine_point_zone_init_from_json(this, json, size)
81  class(combine_point_zone_t), intent(inout) :: this
82  type(json_file), intent(inout) :: json
83  integer, intent(in) :: size
84 
85  ! Json low-level manipulator.
86  type(json_core) :: core
87  ! Pointer to the point_zones JSON object and the individual sources.
88  type(json_value), pointer :: source_object, source_pointer
89  ! Buffer for serializing the json.
90  character(len=:), allocatable :: buffer
91  ! A single source term as its own json_file.
92  type(json_file) :: source_subdict
93  character(len=:), allocatable :: type_name
94  character(len=:), allocatable :: type_string
95 
96  character(len=:), allocatable :: str_read
97  integer :: i, n_zones, i_internal, i_external
98  logical :: found, invert
99 
100  call json_get(json, "name", str_read)
101  call json_get_or_default(json, "invert", invert, .false.)
102  call this%init_base(size, trim(str_read), invert)
103 
104  call json%get_core(core)
105  call json%get('subsets', source_object, found)
106 
107  if (.not. found) call neko_error("No subsets found")
108 
109  this%n_zones = core%count(source_object)
110 
111  ! Allocate arrays if we found things
112  if (this%n_zones .gt. 0) then
113  allocate(this%zones(this%n_zones))
114  end if
115 
116  ! First, count how many external zones we have (external = only "name",
117  ! to be retrieved by the register later).
118  do i = 1, this%n_zones
119  ! Create a new json containing just the subdict for this source.
120  call core%get_child(source_object, i, source_pointer, found)
121  call core%print_to_string(source_pointer, buffer)
122  call source_subdict%load_from_string(buffer)
123 
124  if (.not. source_subdict%valid_path("geometry")) then
125  this%n_external_zones = this%n_external_zones + 1
126  end if
127  end do
128 
129  this%n_internal_zones = this%n_zones - this%n_external_zones
130  if (this%n_external_zones .gt. 0) &
131  allocate(this%names(this%n_external_zones))
132  if (this%n_internal_zones .gt. 0) &
133  allocate(this%internal_zones(this%n_internal_zones))
134 
135  i_internal = 1
136  i_external = 1
137 
138  ! now go through everything again and either construct a point zone or
139  ! save its name for the registry to fill it in later
140  do i = 1, this%n_zones
141 
142  ! Create a new json containing just the subdict for this source.
143  call core%get_child(source_object, i, source_pointer, found)
144  call core%print_to_string(source_pointer, buffer)
145  call source_subdict%load_from_string(buffer)
146 
147  if (source_subdict%valid_path("geometry")) then
148  call point_zone_factory(this%internal_zones(i_internal)%pz, &
149  source_subdict)
150  call assign_point_zone(this%zones(i_internal)%pz, &
151  this%internal_zones(i_internal)%pz)
152  i_internal = i_internal + 1
153  else
154  call json_get(source_subdict, "name", type_name)
155  this%names(i_external) = trim(type_name)
156  i_external = i_external + 1
157  end if
158 
159  end do
160 
161  ! Chcek that we got the proper operator
162  call json_get(json, "operator", this%operator)
163  select case (trim(this%operator))
164  case ("OR")
165  case ("AND")
166  case ("XOR")
167  case default
168  call neko_error("Unknown operator " // trim(this%operator))
169  end select
170 
171  end subroutine combine_point_zone_init_from_json
172 
173  subroutine assign_point_zone(pt, tgt)
174  class(point_zone_t), intent(inout), pointer :: pt
175  class(point_zone_t), intent(inout), target :: tgt
176 
177  pt => tgt
178 
179  end subroutine assign_point_zone
180 
182  subroutine combine_point_zone_free(this)
183  class(combine_point_zone_t), intent(inout) :: this
184 
185  integer :: i
186 
187  if (allocated(this%zones)) then
188  do i = 1, this%n_zones
189  nullify(this%zones(i)%pz)
190  end do
191  deallocate(this%zones)
192  end if
193 
194  if (allocated(this%internal_zones)) then
195  do i = 1, this%n_internal_zones
196  call this%internal_zones(i)%pz%free
197  end do
198  deallocate(this%internal_zones)
199  end if
200 
201  if (allocated(this%names)) deallocate(this%names)
202 
203  this%n_zones = 0
204  this%n_internal_zones = 0
205  this%n_external_zones = 0
206  call this%free_base()
207 
208  end subroutine combine_point_zone_free
209 
219  pure function combine_point_zone_criterion(this, x, y, z, j, k, l, e) &
220  result(is_inside)
221  class(combine_point_zone_t), intent(in) :: this
222  real(kind=rp), intent(in) :: x
223  real(kind=rp), intent(in) :: y
224  real(kind=rp), intent(in) :: z
225  integer, intent(in) :: j
226  integer, intent(in) :: k
227  integer, intent(in) :: l
228  integer, intent(in) :: e
229  logical :: is_inside
230 
231  integer :: i
232 
233  is_inside = this%zones(1)%pz%criterion(x, &
234  y, z, j, k, l, e) .neqv. this%zones(1)%pz%invert
235 
236  do i = 2, this%n_zones
237  select case (trim(this%operator))
238  case ("OR")
239  is_inside = is_inside .or. (this%zones(i)%pz%criterion(x, &
240  y, z, j, k, l, e) .neqv. this%zones(i)%pz%invert)
241 
242  case ("AND")
243  is_inside = is_inside .and. (this%zones(i)%pz%criterion(x, &
244  y, z, j, k, l, e) .neqv. this%zones(i)%pz%invert)
245 
246  case ("XOR")
247  is_inside = is_inside .neqv. (this%zones(i)%pz%criterion(x, &
248  y, z, j, k, l, e).neqv. this%zones(i)%pz%invert)
249 
250  case default
251  end select
252  end do
253 
254  end function combine_point_zone_criterion
255 
256 end module combine_point_zone
Retrieves a parameter by name or assigns a provided default value. In the latter case also adds the m...
Definition: json_utils.f90:53
Retrieves a parameter by name or throws an error.
Definition: json_utils.f90:44
subroutine combine_point_zone_free(this)
Destructor.
subroutine assign_point_zone(pt, tgt)
subroutine combine_point_zone_init_from_json(this, json, size)
Constructor from json object file. Reads.
pure logical function combine_point_zone_criterion(this, x, y, z, j, k, l, e)
Defines the criterion of selection of a GLL point in the combined point zone.
Implements a cylinder geometry subset.
Utilities for retrieving parameters from the case files.
Definition: json_utils.f90:34
Logging routines.
Definition: log.f90:34
type(log_t), public neko_log
Global log stream.
Definition: log.f90:61
integer, parameter, public rp
Global precision used in computations.
Definition: num_types.f90:12
Utilities.
Definition: utils.f90:35
character(:) function, allocatable, public concat_string_array(array, sep, prepend)
Concatenate an array of strings into one string with array items separated by spaces.
Definition: utils.f90:208
A box-shaped point zone.
A point zone that combines different point zones.
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