Neko-TOP
A portable framework for high-order spectral element flow toplogy optimization.
Loading...
Searching...
No Matches
adjoint_lube_source_term.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!
34!
35!
36! I know this is a stupid naming convention...
37! The `lube` aspect came from a paper that attributed this term to out of plane
38! stresses based on lubrication theory.
39!
40! I preffer to think of it as a constraint that penalizes non-binary designs
41!
42! The term is $K \int_\Omega \frac{1}{2}\chi|\mathbf{u}|^2$
43!
44! the corresponding adjoint forcing is $K \chi \mathbf{u}$
46 use num_types, only: rp
47 use field_list, only: field_list_t
48 use json_module, only: json_file
49 use source_term, only: source_term_t
50 use coefs, only: coef_t
51 use field, only: field_t
52 use design, only: design_t
53 use brinkman_design, only: brinkman_design_t
54 use field_math, only: field_addcol3, field_copy, field_cmult
55 use scratch_registry, only: neko_scratch_registry
57 use point_zone, only: point_zone_t
58 use utils, only: neko_error
59 use field_registry, only: neko_field_registry
60 implicit none
61 private
62
64 ! $K \int_\Omega \frac{1}{2}\chi|\mathbf{u}|^2$.
65 type, public, extends(source_term_t) :: adjoint_lube_source_term_t
66
68 type(field_t), pointer :: u => null()
70 type(field_t), pointer :: v => null()
72 type(field_t), pointer :: w => null()
74 type(field_t), pointer :: chi => null()
76 real(kind=rp) :: k
78 class(point_zone_t), pointer :: mask => null()
80 logical :: if_mask
81
82 contains
84 procedure, pass(this) :: init => adjoint_lube_source_term_init_from_json
86 procedure, pass(this) :: init_from_components => &
87 adjoint_lube_source_term_init_from_components
89 procedure, pass(this) :: free => adjoint_lube_source_term_free
91 procedure, pass(this) :: compute_ => adjoint_lube_source_term_compute
93
94contains
101 subroutine adjoint_lube_source_term_init_from_json(this, json, fields, coef, &
102 variable_name)
103 class(adjoint_lube_source_term_t), intent(inout) :: this
104 type(json_file), intent(inout) :: json
105 type(field_list_t), intent(in), target :: fields
106 type(coef_t), intent(in), target :: coef
107 character(len=*), intent(in) :: variable_name
108 ! real(kind=rp), allocatable :: values(:)
109 ! real(kind=rp) :: start_time, end_time
110
111
112 ! we shouldn't be initializing this from JSON
113 ! maybe throw an error?
114
115
116 end subroutine adjoint_lube_source_term_init_from_json
117
127 subroutine adjoint_lube_source_term_init_from_components(this, &
128 f_x, f_y, f_z, design, K, &
129 u, v, w, &
130 mask, if_mask, &
131 coef)
132 class(adjoint_lube_source_term_t), intent(inout) :: this
133 type(field_t), pointer, intent(in) :: f_x, f_y, f_z
134 class(design_t), intent(in), target :: design
135 class(point_zone_t), intent(in), target :: mask
136 type(coef_t), intent(in) :: coef
137 real(kind=rp) :: start_time
138 real(kind=rp) :: end_time
139 type(field_list_t) :: fields
140 logical :: if_mask
141 real(kind=rp) :: k
142 type(field_t), intent(in), target :: u, v, w
143
144 ! I wish you didn't need a start time and end time...
145 ! but I'm just going to set a super big number...
146 start_time = 0.0_rp
147 end_time = 100000000.0_rp
148
149 call this%free()
150
151 ! this is copying the fluid source term init
152 ! We package the fields for the source term to operate on in a field list.
153 call fields%init(3)
154 call fields%assign(1, f_x)
155 call fields%assign(2, f_y)
156 call fields%assign(3, f_z)
157
158 call this%init_base(fields, coef, start_time, end_time)
159
160 ! point everything in the correct places
161 ! NOTE!!!
162 ! this is the primal!
163 this%u => u
164 this%v => v
165 this%w => w
166
167 select type (design)
168 type is (brinkman_design_t)
169 this%chi => neko_field_registry%get_field("brinkman_amplitude")
170 class default
171 call neko_error('Unknown design type')
172 end select
173
174 this%K = k
175 this%if_mask = if_mask
176 if (this%if_mask) then
177 this%mask => mask
178 end if
179
180 end subroutine adjoint_lube_source_term_init_from_components
181
183 subroutine adjoint_lube_source_term_free(this)
184 class(adjoint_lube_source_term_t), intent(inout) :: this
185
186 call this%free_base()
187 end subroutine adjoint_lube_source_term_free
188
193 subroutine adjoint_lube_source_term_compute(this, t, tstep)
194 class(adjoint_lube_source_term_t), intent(inout) :: this
195 real(kind=rp), intent(in) :: t
196 integer, intent(in) :: tstep
197 type(field_t), pointer :: fu, fv, fw
198 type(field_t), pointer :: work
199 integer :: temp_indices(1)
200
201 fu => this%fields%get_by_index(1)
202 fv => this%fields%get_by_index(2)
203 fw => this%fields%get_by_index(3)
204
205 ! BE SO CAREFUL HERE
206 ! It make look the same as the Brinkman term, but it's assumed that
207 ! this source term acts on the adjoint, and the u,v,w here come from
208 ! the primal
209 call neko_scratch_registry%request_field(work, temp_indices(1))
210 call field_copy(work, this%chi)
211
212 ! scale by K
213 call field_cmult(work, this%K)
214
215 ! mask
216 if (this%if_mask) then
217 call mask_exterior_const(work, this%mask, 0.0_rp)
218 end if
219
220 ! multiple and add the RHS
221 call field_addcol3(fu, this%u, work)
222 call field_addcol3(fv, this%v, work)
223 call field_addcol3(fw, this%w, work)
224 call neko_scratch_registry%relinquish_field(temp_indices)
225
226 end subroutine adjoint_lube_source_term_compute
227
Implements the adjoint_lube_source_term_t type.
Implements the design_t.
Definition design.f90:34
Some common Masking operations we may need.
Definition mask_ops.f90:34
A adjoint source term corresponding to an objective of.
A topology optimization design variable.
An abstract design type.
Definition design.f90:50