Neko-TOP
A portable framework for high-order spectral element flow toplogy optimization.
Loading...
Searching...
No Matches
simulation_adjoint.f90
1! Copyright (c) 2020-2021, 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 mpi_f08, only: mpi_wtime
36 use case, only: case_t
37 use num_types, only: rp, dp
38 use time_scheme_controller, only: time_scheme_controller_t
39 use file, only: file_t
40 use logger, only: log_size, neko_log
41 use jobctrl, only: jobctrl_time_limit
42 use field, only: field_t
43 use profiler, only: profiler_start, profiler_stop, &
44 profiler_start_region, profiler_end_region
45 use json_utils, only: json_get_or_default
46 use time_step_controller, only: time_step_controller_t
47 use adjoint_case, only: adjoint_case_t
48 implicit none
49 private
50
51 public :: solve_adjoint, simulation_restart
52
53contains
54
55 ! Compute the simcomp_test field.
56 subroutine solve_adjoint(this)
57 type(adjoint_case_t), intent(inout) :: this
58
59 real(kind=rp) :: t_adj
60 real(kind=dp) :: start_time_org, start_time, end_time
61 character(len=LOG_SIZE) :: log_buf
62 integer :: tstep_adj
63 logical :: output_at_end
64 type(time_step_controller_t) :: dt_controller
65
66 ! ------------------------------------------------------------------------ !
67 ! Computation of the adjoint field.
68 !
69 ! This is where the actual computation of the adjoint field should be
70 ! implemented. This will so far just be a steady state field based on the
71 ! current state of the fluid fields.
72
73 ! ------------------------------------------------------------------------ !
74
75 t_adj = 0d0
76 tstep_adj = 0
77 call neko_log%section('Starting adjoint')
78 write(log_buf, '(A,E15.7,A,E15.7,A)') 'T : [', 0d0, ', ', &
79 this%case%time%end_time, ')'
80 call neko_log%message(log_buf)
81 call dt_controller%init(this%case%params)
82 if (.not. dt_controller%if_variable_dt) then
83 write(log_buf, '(A, E15.7)') 'dt : ', this%case%time%dt
84 call neko_log%message(log_buf)
85 else
86 write(log_buf, '(A, E15.7)') 'CFL : ', dt_controller%set_cfl
87 call neko_log%message(log_buf)
88 end if
89
91 call neko_log%section('Postprocessing')
92 ! call this%case%q%eval(t_adj, this%case%time%dt, tstep_adj)
93 call this%output_controller%execute(this%case%time)
94
95 ! HARRY
96 ! ok this I guess this is techincally where we set the initial condition
97 ! of adjoint yeh?
98 call this%case%usr%user_init_modules(t_adj, this%fluid_adj%u_adj, &
99 this%fluid_adj%v_adj, this%fluid_adj%w_adj,&
100 this%fluid_adj%p_adj, this%fluid_adj%c_Xh, this%case%params)
101 call neko_log%end_section()
102 call neko_log%newline()
103
104 call profiler_start
105 start_time_org = mpi_wtime()
106
107 do while (t_adj .lt. this%case%time%end_time .and. &
108 (.not. jobctrl_time_limit()))
109 call profiler_start_region('Time-Step')
110 tstep_adj = tstep_adj + 1
111 start_time = mpi_wtime()
112
113 call this%case%time%status()
114 call neko_log%message(log_buf)
115 call neko_log%begin()
116
117 ! write(log_buf, '(A,E15.7,1x,A,E15.7)') 'CFL:', cfl, 'dt:', &
118 ! this%case%time%dt
119 call neko_log%message(log_buf)
120 call simulation_settime(t_adj, this%case%time%dt, &
121 this%case%fluid%ext_bdf, this%case%time%tlag, &
122 this%case%time%dtlag, tstep_adj)
123
124
125 ! Scalar step
126 ! (Note that for the adjoint we should the scalar_adj first)
127 if (allocated(this%scalar_adj)) then
128 start_time = mpi_wtime()
129 call neko_log%section(' Adjoint scalar')
130 call this%scalar_adj%step(t_adj, tstep_adj, this%case%time%dt, &
131 this%case%fluid%ext_bdf, dt_controller)
132 end_time = mpi_wtime()
133 write(log_buf, '(A,E15.7,A,E15.7)') &
134 'Elapsed time (s):', end_time-start_time_org, ' Step time:', &
135 end_time-start_time
136 call neko_log%end_section(log_buf)
137 end if
138
139 call neko_log%section('Adjoint fluid')
140 call this%fluid_adj%step(t_adj, tstep_adj, this%case%time%dt, &
141 this%case%fluid%ext_bdf, dt_controller)
142 end_time = mpi_wtime()
143 write(log_buf, '(A,E15.7,A,E15.7)') &
144 'Elapsed time (s):', end_time-start_time_org, ' Step time:', &
145 end_time-start_time
146 call neko_log%end_section(log_buf)
147
148
149 call neko_log%section('Postprocessing')
150
151 ! call this%case%q%eval(t_adj, this%case%time%dt, tstep_adj)
152 call this%output_controller%execute(this%case%time)
153
154 call neko_log%end_section()
155
156 call neko_log%end()
157 call profiler_end_region
158 end do
159 call profiler_stop
160
161 call json_get_or_default(this%case%params, 'case.output_at_end',&
162 output_at_end, .true.)
163 call this%output_controller%execute(this%case%time, output_at_end)
164
165 if (.not. (output_at_end) .and. t_adj .lt. this%case%time%end_time) then
166 call simulation_joblimit_chkp(this%case, t_adj)
167 end if
168
169 call this%case%usr%user_finalize_modules(t_adj, this%case%params)
170
171 call neko_log%end_section('Normal end.')
172
173 end subroutine solve_adjoint
174
175 subroutine simulation_settime(t, dt, ext_bdf, tlag, dtlag, step)
176 real(kind=rp), intent(inout) :: t
177 real(kind=rp), intent(in) :: dt
178 type(time_scheme_controller_t), intent(inout) :: ext_bdf
179 real(kind=rp), dimension(10) :: tlag
180 real(kind=rp), dimension(10) :: dtlag
181 integer, intent(in) :: step
182 integer :: i
183
184
185 do i = 10, 2, -1
186 tlag(i) = tlag(i-1)
187 dtlag(i) = dtlag(i-1)
188 end do
189
190 dtlag(1) = dt
191 tlag(1) = t
192 if (ext_bdf%ndiff .eq. 0) then
193 dtlag(2) = dt
194 tlag(2) = t
195 end if
196
197 t = t + dt
198
199 call ext_bdf%set_coeffs(dtlag)
200
201 end subroutine simulation_settime
202
204 subroutine simulation_restart(C, t)
205 type(case_t), intent(inout) :: c
206 real(kind=rp), intent(inout) :: t
207 integer :: i
208 type(file_t) :: chkpf, previous_meshf
209 character(len=LOG_SIZE) :: log_buf
210 character(len=:), allocatable :: restart_file
211 character(len=:), allocatable :: restart_mesh_file
212 real(kind=rp) :: tol
213 logical :: found
214
215 call c%params%get('case.restart_file', restart_file, found)
216 call c%params%get('case.restart_mesh_file', restart_mesh_file, found)
217
218 if (found) then
219 previous_meshf = file_t(trim(restart_mesh_file))
220 call previous_meshf%read(c%fluid%chkp%previous_mesh)
221 end if
222
223 call c%params%get('case.mesh2mesh_tolerance', tol,&
224 found)
225
226 if (found) c%fluid%chkp%mesh2mesh_tol = tol
227
228 chkpf = file_t(trim(restart_file))
229 call chkpf%read(c%fluid%chkp)
230 c%time%dtlag = c%fluid%chkp%dtlag
231 c%time%tlag = c%fluid%chkp%tlag
232
233 !Free the previous mesh, dont need it anymore
234 call c%fluid%chkp%previous_mesh%free()
235 do i = 1, size(c%time%dtlag)
236 call c%fluid%ext_bdf%set_coeffs(c%time%dtlag)
237 end do
238
239 call c%fluid%restart(c%chkp)
240 if (allocated(c%scalar)) call c%scalar%restart(c%chkp)
241
242 t = c%fluid%chkp%restart_time()
243 call neko_log%section('Restarting from checkpoint')
244 write(log_buf, '(A,A)') 'File : ', trim(restart_file)
245 call neko_log%message(log_buf)
246 write(log_buf, '(A,E15.7)') 'Time : ', t
247 call neko_log%message(log_buf)
248 call neko_log%end_section()
249
250 call c%output_controller%set_counter(c%time)
251 end subroutine simulation_restart
252
254 subroutine simulation_joblimit_chkp(C, t)
255 type(case_t), intent(inout) :: c
256 real(kind=rp), intent(inout) :: t
257 type(file_t) :: chkpf
258 character(len=:), allocatable :: chkp_format
259 character(len=LOG_SIZE) :: log_buf
260 character(len=10) :: format_str
261 logical :: found
262
263 call c%params%get('case.checkpoint_format', chkp_format, found)
264 call c%fluid%chkp%sync_host()
265 format_str = '.chkp'
266 if (found) then
267 if (chkp_format .eq. 'hdf5') then
268 format_str = '.h5'
269 end if
270 end if
271 chkpf = file_t('joblimit'//trim(format_str))
272 call chkpf%write(c%fluid%chkp, t)
273 write(log_buf, '(A)') '! saving checkpoint >>>'
274 call neko_log%message(log_buf)
275
276 end subroutine simulation_joblimit_chkp
277
278
279end module simulation_adjoint
280
281
Adjoint simulation driver.
Adjoint case type. Todo: This should Ideally be a subclass of case_t, however, that is not yet suppor...