Neko-TOP
A portable framework for high-order spectral element flow toplogy optimization.
Loading...
Searching...
No Matches
design_simple.f90
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 the `simple_design_t` type.
34module simple_design
35 use num_types, only: rp, sp
36 use field, only: field_t
37 use json_module, only: json_file
38 use mapping, only: mapping_t
39 use pde_filter, only: pde_filter_t
41 use coefs, only: coef_t
42 use scratch_registry, only: neko_scratch_registry
43 use fld_file_output, only: fld_file_output_t
44 use point_zone_registry, only: neko_point_zone_registry
45 use point_zone, only: point_zone_t
47 use neko_config, only: neko_bcknd_device
48 use device, only: device_memcpy, host_to_device
49 use design, only: design_t
50 use math, only: rzero
51 use simulation_m, only: simulation_t
52 use json_module, only: json_file
53 use json_utils, only: json_get
55 use vector, only: vector_t
56 use math, only: copy
57 use field_registry, only: neko_field_registry
58 implicit none
59 private
60
62 type, extends(design_t), public :: simple_design_t
63 private
64
65 type(vector_t) :: values
66 type(vector_t) :: x
67 type(vector_t) :: y
68 type(vector_t) :: z
69
70 contains
71
72 ! ----------------------------------------------------------------------- !
73 ! Initializations
74
76 generic, public :: init => init_from_json, init_from_components
78 procedure, pass(this) :: init_from_json => &
79 design_simple_init_from_json
81 procedure, pass(this) :: init_from_components => &
82 design_simple_init_from_components
83
85 procedure, pass(this) :: add_mapping => design_simple_add_mapping
86
88 procedure, pass(this) :: get_values => design_simple_get_values
90 procedure, pass(this) :: get_x => design_simple_get_x
92 procedure, pass(this) :: get_y => design_simple_get_y
94 procedure, pass(this) :: get_z => design_simple_get_z
95
97 procedure, pass(this) :: update_design => design_simple_update_design
98
100 procedure, pass(this) :: map_forward => design_simple_map_forward
101
103 procedure, pass(this) :: map_backward => design_simple_map_backward
104
106 procedure, pass(this) :: write => design_simple_write
107
109 procedure, pass(this) :: free => design_simple_free
110
111 end type simple_design_t
112
113contains
114
116 subroutine design_simple_init_from_json(this, parameters)
117 class(simple_design_t), intent(inout) :: this
118 type(json_file), intent(inout) :: parameters
119 character(len=:), allocatable :: type
120 integer :: n, nx, ny, nz, i, j, k
121 real(kind=rp), dimension(:), allocatable :: limits
122 type(vector_t) :: x, y, z
123
124 call json_get(parameters, 'optimization.design.domain.type', type)
125
126 select case (trim(type))
127 case ("box")
128 call json_get(parameters, 'optimization.design.domain.nx', nx)
129 call json_get(parameters, 'optimization.design.domain.ny', ny)
130 call json_get(parameters, 'optimization.design.domain.nz', nz)
131 call json_get(parameters, 'optimization.design.domain.limits', limits)
132 n = nx * ny * nz
133
134 call x%init(n)
135 call y%init(n)
136 call z%init(n)
137
138 do i = 1, nx
139 do j = 1, ny
140 do k = 1, nz
141 x%x(i) = limits(1) + (limits(2) - limits(1)) * &
142 real(i - 1, kind=rp) / real(nx, kind=rp)
143 y%x(i) = limits(3) + (limits(4) - limits(3)) * &
144 real(j - 1, kind=rp) / real(ny, kind=rp)
145 z%x(i) = limits(5) + (limits(6) - limits(5)) * &
146 real(k - 1, kind=rp) / real(nz, kind=rp)
147 end do
148 end do
149 end do
150
151 end select
152
153 call this%init_from_components(n, x, y, z)
154
155 end subroutine design_simple_init_from_json
156
157 subroutine design_simple_init_from_components(this, n, x, y, z)
158 class(simple_design_t), intent(inout) :: this
159 integer, intent(in) :: n
160 type(vector_t), intent(in) :: x, y, z
161
162 call this%init_base(n)
163
164 call this%values%init(n)
165 this%x = x
166 this%y = y
167 this%z = z
168
169 end subroutine design_simple_init_from_components
170
172 subroutine design_simple_free(this)
173 class(simple_design_t), intent(inout) :: this
174
175 call this%free_base()
176 call this%values%free()
177 call this%x%free()
178 call this%y%free()
179 call this%z%free()
180
181 end subroutine design_simple_free
182
184 subroutine design_simple_add_mapping(this, parameters, simulation)
185 class(simple_design_t), intent(inout) :: this
186 type(json_file), intent(inout) :: parameters
187 type(simulation_t), intent(inout) :: simulation
188
189 end subroutine design_simple_add_mapping
190
191
192 subroutine design_simple_map_forward(this)
193 class(simple_design_t), intent(inout) :: this
194
195
196 end subroutine design_simple_map_forward
197
198 function design_simple_get_values(this) result(values)
199 class(simple_design_t), intent(in) :: this
200 type(vector_t) :: values
201
202 values = this%values
203
204 end function design_simple_get_values
205
206 function design_simple_get_x(this) result(x)
207 class(simple_design_t), intent(in) :: this
208 type(vector_t) :: x
209
210 x = this%x
211
212 end function design_simple_get_x
213
214 function design_simple_get_y(this) result(y)
215 class(simple_design_t), intent(in) :: this
216 type(vector_t) :: y
217
218 y = this%y
219
220 end function design_simple_get_y
221
222 function design_simple_get_z(this) result(z)
223 class(simple_design_t), intent(in) :: this
224 type(vector_t) :: z
225
226 z = this%z
227
228 end function design_simple_get_z
229
230 subroutine design_simple_update_design(this, values)
231 class(simple_design_t), intent(inout) :: this
232 type(vector_t), intent(inout) :: values
233
234 this%values = values
235
236 end subroutine design_simple_update_design
237
238 subroutine design_simple_map_backward(this, sensitivity)
239 class(simple_design_t), intent(inout) :: this
240 type(vector_t), intent(in) :: sensitivity
241
242 end subroutine design_simple_map_backward
243
244 subroutine design_simple_write(this, idx)
245 class(simple_design_t), intent(inout) :: this
246 integer, intent(in) :: idx
247
248 end subroutine design_simple_write
249
250end module simple_design
Implements the design_t.
Definition design.f90:34
Mappings to be applied to a scalar field.
Definition mapping.f90:35
Some common Masking operations we may need.
Definition mask_ops.f90:34
A PDE based filter.
A RAMP mapping of coefficients.
Implements the simple_brinkman_source_term_t type.
Implements the steady_problem_t type.
An abstract design type.
Definition design.f90:50
Base abstract class for mapping.
Definition mapping.f90:45
A PDE based filter mapping , see Lazarov & O. Sigmund 2010, by solving an equation of the form .
A RAMP mapping of coefficients This is the standard RAMP described in https://doi....
A topology optimization design variable.