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