Neko-TOP
A portable framework for high-order spectral element flow toplogy optimization.
Loading...
Searching...
No Matches
topopt_brinkman_source.f90
Go to the documentation of this file.
1! Copyright (c) 2023, 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!
35 use num_types, only: rp, dp
36 use field, only: field_t
37 use field_list, only: field_list_t
38 use json_utils, only: json_get, json_get_or_default, json_extract_item
39 use field_registry, only: neko_field_registry
40 use source_term, only: source_term_t
41 use coefs, only: coef_t
42 use neko_config, only: neko_bcknd_device
43 use utils, only: neko_error
44 use field_math, only: field_subcol3
45 use file, only: file_t
46 use tri_mesh, only: tri_mesh_t
47 use device, only: device_memcpy, host_to_device
48 use filters, only: smooth_step_field, step_function_field, permeability_field
49 use signed_distance, only: signed_distance_field
50 use profiler, only: profiler_start_region, profiler_end_region
51 use json_module, only: json_core, json_value, json_file
52 use point_zone, only: point_zone_t
53 use point_zone_registry, only: neko_point_zone_registry
54 use aabb, only: aabb_t, get_aabb
55 implicit none
56
57
58 private
59
63 type, public, extends(source_term_t) :: topopt_brinkman_source_term_t
64 private
65
67 type(field_t), pointer :: indicator => null()
69 type(field_t), pointer :: brinkman => null()
70 contains
72 procedure, public, pass(this) :: init => &
75 procedure, public, pass(this) :: free => brinkman_source_term_free
77 procedure, public, pass(this) :: compute_ => brinkman_source_term_compute
79 ! procedure, public, pass(this) :: update_resistance
80
81 ! ----------------------------------------------------------------------- !
82 ! Private methods
83 procedure, pass(this) :: init_boundary_mesh
84 procedure, pass(this) :: init_point_zone
86
87contains
88
89 ! ========================================================================== !
90 ! Public methods
91
96 subroutine brinkman_source_term_init_from_json(this, json, fields, coef)
97 class(topopt_brinkman_source_term_t), intent(inout) :: this
98 type(json_file), intent(inout) :: json
99 type(field_list_t), intent(inout), target :: fields
100 type(coef_t), target, intent(inout) :: coef
101 real(kind=rp) :: start_time, end_time
102
103 character(len=:), allocatable :: filter_type
104 real(kind=rp), dimension(:), allocatable :: brinkman_limits
105 real(kind=rp) :: brinkman_penalty
106
107 type(json_value), pointer :: json_object_list
108 type(json_core) :: core
109
110 character(len=:), allocatable :: object_type
111 type(json_file) :: object_settings
112 integer :: n_regions
113 integer :: i
114
115 ! Mandatory fields for the general source term
116 call json_get_or_default(json, "start_time", start_time, 0.0_rp)
117 call json_get_or_default(json, "end_time", end_time, huge(0.0_rp))
118
119 ! Read the options for the permeability field
120 call json_get(json, 'brinkman.limits', brinkman_limits)
121 call json_get(json, 'brinkman.penalty', brinkman_penalty)
122
123 if (size(brinkman_limits) .ne. 2) then
124 call neko_error('brinkman_limits must be a 2 element array of reals')
125 end if
126
127 call this%free()
128 call this%init_base(fields, coef, start_time, end_time)
129
130 ! ------------------------------------------------------------------------ !
131 ! Allocate the permeability and indicator field
132
133 if (neko_field_registry%field_exists('brinkman_indicator') &
134 .or. neko_field_registry%field_exists('brinkman')) then
135 call neko_error('Brinkman field already exists.')
136 end if
137
138 call neko_field_registry%add_field(coef%dof, 'brinkman_indicator')
139 this%indicator => &
140 neko_field_registry%get_field_by_name('brinkman_indicator')
141
142 call neko_field_registry%add_field(coef%dof, 'brinkman')
143 this%brinkman => neko_field_registry%get_field_by_name('brinkman')
144
145 ! ------------------------------------------------------------------------ !
146 ! Select which constructor should be called
147
148 call json%get('objects', json_object_list)
149 call json%info('objects', n_children = n_regions)
150 call json%get_core(core)
151
152 do i = 1, n_regions
153 call json_extract_item(core, json_object_list, i, object_settings)
154 call json_get_or_default(object_settings, 'type', object_type, 'none')
155
156 select case (object_type)
157 case ('boundary_mesh')
158 call this%init_boundary_mesh(object_settings)
159 case ('point_zone')
160 call this%init_point_zone(object_settings)
161
162 case ('none')
163 call object_settings%print()
164 call neko_error('Brinkman source term objects require a region type')
165 case default
166 call neko_error('Brinkman source term unknown region type')
167 end select
168
169 end do
170
171 ! Run filter on the full indicator field to smooth it out.
172 call json_get_or_default(json, 'filter.type', filter_type, 'none')
173
174 select case (filter_type)
175 case ('none')
176 ! Do nothing
177 case default
178 call neko_error('Brinkman source term unknown filter type')
179 end select
180
181 ! ------------------------------------------------------------------------ !
182 ! Compute the permeability field
183
184 call permeability_field(this%brinkman, this%indicator, &
185 brinkman_limits(1), brinkman_limits(2), brinkman_penalty)
186
187 ! Copy the permeability field to the device
188 if (neko_bcknd_device .eq. 1) then
189 call device_memcpy(this%brinkman%x, this%brinkman%x_d, &
190 this%brinkman%dof%size(), host_to_device, .true.)
191 end if
192
194
197 class(topopt_brinkman_source_term_t), intent(inout) :: this
198
199 this%brinkman => null()
200 call this%free_base()
201 end subroutine brinkman_source_term_free
202
206 subroutine brinkman_source_term_compute(this, t, tstep)
207 class(topopt_brinkman_source_term_t), intent(inout) :: this
208 real(kind=rp), intent(in) :: t
209 integer, intent(in) :: tstep
210 type(field_t), pointer :: u, v, w, fu, fv, fw
211 integer :: n
212
213 n = this%fields%item_size(1)
214
215 u => neko_field_registry%get_field('u')
216 v => neko_field_registry%get_field('v')
217 w => neko_field_registry%get_field('w')
218
219 fu => this%fields%get(1)
220 fv => this%fields%get(2)
221 fw => this%fields%get(3)
222
223 call field_subcol3(fu, u, this%brinkman, n)
224 call field_subcol3(fv, v, this%brinkman, n)
225 call field_subcol3(fw, w, this%brinkman, n)
226
227 end subroutine brinkman_source_term_compute
228
229 ! ========================================================================== !
230 ! Private methods
231
233 subroutine init_boundary_mesh(this, json)
234 class(topopt_brinkman_source_term_t), intent(inout) :: this
235 type(json_file), intent(inout) :: json
236
237 ! Options
238 character(len=:), allocatable :: mesh_file_name
239 character(len=:), allocatable :: distance_transform
240 character(len=:), allocatable :: filter_type
241 character(len=:), allocatable :: mesh_transform
242
243 ! Read the options for the boundary mesh
244 type(file_t) :: mesh_file
245 type(tri_mesh_t) :: boundary_mesh
246 real(kind=rp) :: scalar_r
247 real(kind=dp) :: scalar_d
248
249 ! Mesh transform options variables
250 real(kind=dp), dimension(:), allocatable :: box_min, box_max
251 logical :: keep_aspect_ratio
252 real(kind=dp), dimension(3) :: scaling
253 real(kind=dp), dimension(3) :: translation
254 type(field_t) :: temp_field
255 type(aabb_t) :: mesh_box, target_box
256 integer :: idx_p
257
258 ! ------------------------------------------------------------------------ !
259 ! Read the options for the boundary mesh
260
261 call json_get(json, 'name', mesh_file_name)
262
263 ! Settings on how to filter the design field
264 call json_get(json, 'distance_transform.type', distance_transform)
265
266 ! ------------------------------------------------------------------------ !
267 ! Load the immersed boundary mesh
268
269 mesh_file = file_t(mesh_file_name)
270 call mesh_file%read(boundary_mesh)
271
272 if (boundary_mesh%nelv .eq. 0) then
273 call neko_error('No elements in the boundary mesh')
274 end if
275
276 ! ------------------------------------------------------------------------ !
277 ! Transform the mesh if specified.
278
279 call json_get_or_default(json, 'mesh_transform.type', &
280 mesh_transform, 'none')
281
282 select case (mesh_transform)
283 case ('none')
284 ! Do nothing
285 case ('bounding_box')
286 call json_get(json, 'mesh_transform.box_min', box_min)
287 call json_get(json, 'mesh_transform.box_max', box_max)
288 call json_get_or_default(json, 'mesh_transform.keep_aspect_ratio', &
289 keep_aspect_ratio, .true.)
290
291 if (size(box_min) .ne. 3 .or. size(box_max) .ne. 3) then
292 call neko_error('Case file: mesh_transform. &
293 &box_min and box_max must be 3 element arrays of reals')
294 end if
295
296 call target_box%init(box_min, box_max)
297
298 mesh_box = get_aabb(boundary_mesh)
299
300 scaling = target_box%get_diagonal() / mesh_box%get_diagonal()
301 if (keep_aspect_ratio) then
302 scaling = minval(scaling)
303 end if
304
305 translation = - scaling * mesh_box%get_min() + target_box%get_min()
306
307 do idx_p = 1, boundary_mesh%mpts
308 boundary_mesh%points(idx_p)%x = &
309 scaling * boundary_mesh%points(idx_p)%x + translation
310 end do
311
312 case default
313 call neko_error('Unknown mesh transform')
314 end select
315
316 ! ------------------------------------------------------------------------ !
317 ! Compute the permeability field
318
319 ! Assign the signed distance field to all GLL points in the permeability
320 ! field. Initally we just run a brute force loop over all GLL points and
321 ! compute the signed distance function. This should be replaced with a
322 ! more efficient method, such as a tree search.
323
324 call temp_field%init(this%indicator%dof)
325
326 ! Select how to transform the distance field to a design field
327 select case (distance_transform)
328 case ('smooth_step')
329 call json_get(json, 'distance_transform.value', scalar_d)
330 scalar_r = real(scalar_d, kind=rp)
331
332 call signed_distance_field(temp_field, boundary_mesh, scalar_d)
333 call smooth_step_field(temp_field, scalar_r, 0.0_rp)
334
335 case ('step')
336
337 call json_get(json, 'distance_transform.value', scalar_d)
338
339 call signed_distance_field(temp_field, boundary_mesh, scalar_d)
340 call step_function_field(temp_field, scalar_r, 1.0_rp, 0.0_rp)
341
342 case default
343 call neko_error('Unknown distance transform')
344 end select
345
346 ! ------------------------------------------------------------------------ !
347 ! Run filter on the temporary indicator field to smooth it out.
348 call json_get_or_default(json, 'filter.type', filter_type, 'none')
349
350 select case (filter_type)
351 case ('none')
352 ! Do nothing
353 case default
354 call neko_error('Unknown filter type')
355 end select
356
357 ! Update the global indicator field by max operator
358 this%indicator%x = max(this%indicator%x, temp_field%x)
359
360 end subroutine init_boundary_mesh
361
363 subroutine init_point_zone(this, json)
364 class(topopt_brinkman_source_term_t), intent(inout) :: this
365 type(json_file), intent(inout) :: json
366
367 ! Options
368 character(len=:), allocatable :: zone_name
369 character(len=:), allocatable :: filter_type
370
371 type(field_t) :: temp_field
372 class(point_zone_t), pointer :: my_point_zone
373 integer :: i
374
375 ! ------------------------------------------------------------------------ !
376 ! Read the options for the point zone
377
378 call json_get(json, 'name', zone_name)
379 call json_get_or_default(json, 'filter.type', filter_type, 'none')
380
381 ! Compute the indicator field
382
383 call temp_field%init(this%indicator%dof)
384
385 my_point_zone => neko_point_zone_registry%get_point_zone(zone_name)
386
387 do i = 1, my_point_zone%size
388 temp_field%x(my_point_zone%mask(i), 1, 1, 1) = 1.0_rp
389 end do
390
391 ! Run filter on the temporary indicator field to smooth it out.
392
393 select case (filter_type)
394 case ('none')
395 ! Do nothing
396 case default
397 call neko_error('Unknown filter type')
398 end select
399
400 ! Update the global indicator field by max operator
401 this%indicator%x = max(this%indicator%x, temp_field%x)
402
403 end subroutine init_point_zone
404
Implements the brinkman_source_term_t type.
subroutine brinkman_source_term_free(this)
Destructor.
subroutine brinkman_source_term_init_from_json(this, json, fields, coef)
The common constructor using a JSON object.
subroutine brinkman_source_term_compute(this, t, tstep)
Computes the source term and adds the result to fields.
subroutine init_boundary_mesh(this, json)
Initializes the source term from a boundary mesh.
subroutine init_point_zone(this, json)
Initializes the source term from a point zone.
A Brinkman source term. The region and strength are controlled by assigning regions types and brinkma...