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_state, only : time_state_t
47 use time_step_controller, only: time_step_controller_t
48 use adjoint_case, only: adjoint_case_t
49 implicit none
50 private
51
52 public :: simulation_adjoint_init, simulation_adjoint_step, &
53 simulation_adjoint_finalize, simulation_adjoint_restart
54
55contains
56
57
59 subroutine simulation_adjoint_init(C, dt_controller)
60 type(adjoint_case_t), intent(inout) :: c
61 type(time_step_controller_t), intent(inout) :: dt_controller
62 character(len=LOG_SIZE) :: log_buf
63
64 ! Write the initial logging message
65 call neko_log%section('Adjoint Starting simulation')
66 write(log_buf, '(A, E15.7,A,E15.7,A)') &
67 'T : [', c%time%t, ',', c%time%end_time, ']'
68 call neko_log%message(log_buf)
69 if (.not. dt_controller%is_variable_dt) then
70 write(log_buf, '(A, E15.7)') 'dt : ', c%time%dt
71 else
72 write(log_buf, '(A, E15.7)') 'CFL : ', dt_controller%cfl_trg
73 end if
74 call neko_log%message(log_buf)
75
76 ! Call stats, samplers and user-init before time loop
77 call neko_log%section('Postprocessing')
78 call c%output_controller%execute(c%time)
79
80 call c%case%user%initialize(c%time)
81 call neko_log%end_section()
82 call neko_log%newline()
83
84 end subroutine simulation_adjoint_init
85
87 subroutine simulation_adjoint_finalize(C)
88 type(adjoint_case_t), intent(inout) :: c
89 logical :: output_at_end
90
91 ! Run a final output if specified in the json
92 call json_get_or_default(c%case%params, 'case.output_at_end', &
93 output_at_end, .true.)
94 call c%output_controller%execute(c%time, output_at_end)
95
96 if (.not. (output_at_end) .and. c%time%t .lt. c%time%end_time) then
97 call simulation_adjoint_joblimit_chkp(c, c%time%t)
98 end if
99
100 ! Finalize the user modules
101 call c%case%user%finalize(c%time)
102
103 call neko_log%end_section('Normal end.')
104
105 end subroutine simulation_adjoint_finalize
106
108 subroutine simulation_adjoint_step(C, dt_controller, cfl, tstep_loop_start_time)
109 type(adjoint_case_t), intent(inout) :: c
110 real(kind=rp), intent(inout) :: cfl
111 type(time_step_controller_t), intent(inout) :: dt_controller
112 real(kind=dp), intent(in) :: tstep_loop_start_time
113 real(kind=dp) :: start_time, end_time, tstep_start_time
114 character(len=LOG_SIZE) :: log_buf
115
116 ! Setup the time step, and start time
117 call profiler_start_region('Time-Step Adjoint')
118 c%time%tstep = c%time%tstep + 1
119 start_time = mpi_wtime()
120 tstep_start_time = start_time
121
122 ! Compute the next time step
123 ! NOTE. we should be wary here since CFL is based on the convective velocity
124 ! not the adjoint velocity
125 cfl = c%fluid_adj%compute_cfl(c%time%dt)
126 call dt_controller%set_dt(c%time, cfl)
127 if (dt_controller%is_variable_dt) cfl = c%fluid_adj%compute_cfl(c%time%dt)
128
129 ! Calculate the cfl after the possibly varied dt
130 ! cfl = C%fluid_adj%compute_cfl(C%time%dt)
131
132 ! Advance time step from t to t+dt and print the status
133 call simulation_settime(c%time, c%fluid_adj%ext_bdf)
134 call c%time%status()
135 call neko_log%begin()
136
137 write(log_buf, '(A,E15.7,1x,A,E15.7)') 'CFL:', cfl, 'dt:', c%time%dt
138 call neko_log%message(log_buf)
139
140 ! Scalar step
141 ! (Note that for the adjoint we should the adjoint_scalars first)
142 if (allocated(c%adjoint_scalars)) then
143 start_time = mpi_wtime()
144 call neko_log%section('Adjoint scalar')
145 call c%adjoint_scalars%step(c%time, &
146 c%case%fluid%ext_bdf, dt_controller)
147 end_time = mpi_wtime()
148 write(log_buf, '(A,E15.7)') &
149 'Scalar step time: ', end_time-start_time
150 call neko_log%end_section(log_buf)
151 end if
152
153 ! Fluid step
154 call neko_log%section('Adjoint fluid')
155 call c%fluid_adj%step(c%time, dt_controller)
156 end_time = mpi_wtime()
157 write(log_buf, '(A,E15.7)') &
158 'Fluid step time (s): ', end_time-start_time
159 call neko_log%end_section(log_buf)
160
161 ! Postprocessing
162 call neko_log%section('Postprocessing')
163
164 ! Run any IO needed.
165 call c%output_controller%execute(c%time)
166
167 call neko_log%end_section()
168
169 ! End the step and print summary
170 end_time = mpi_wtime()
171 call neko_log%section('Step summary')
172 write(log_buf, '(A,I8,A,E15.7)') &
173 'Total time for step ', c%time%tstep, ' (s): ', end_time-tstep_start_time
174 call neko_log%message(log_buf)
175 write(log_buf, '(A,E15.7)') &
176 'Total elapsed time (s): ', end_time-tstep_loop_start_time
177 call neko_log%message(log_buf)
178
179 call neko_log%end_section()
180 call neko_log%end()
181 call profiler_end_region
182
183 end subroutine simulation_adjoint_step
184
185 subroutine simulation_settime(time, ext_bdf)
186 type(time_state_t), intent(inout) :: time
187 type(time_scheme_controller_t), intent(inout), allocatable :: ext_bdf
188 integer :: i
189
190 if (allocated(ext_bdf)) then
191 do i = 10, 2, -1
192 time%tlag(i) = time%tlag(i-1)
193 time%dtlag(i) = time%dtlag(i-1)
194 end do
195
196 time%dtlag(1) = time%dt
197 time%tlag(1) = time%t
198 if (ext_bdf%ndiff .eq. 0) then
199 time%dtlag(2) = time%dt
200 time%tlag(2) = time%t
201 end if
202
203 call ext_bdf%set_coeffs(time%dtlag)
204 end if
205
206 time%t = time%t + time%dt
207
208 end subroutine simulation_settime
209
211 subroutine simulation_adjoint_restart(C)
212 type(adjoint_case_t), intent(inout) :: c
213 integer :: i
214 type(file_t) :: chkpf, previous_meshf
215 character(len=LOG_SIZE) :: log_buf
216 character(len=:), allocatable :: restart_file
217 character(len=:), allocatable :: restart_mesh_file
218 real(kind=rp) :: tol
219 logical :: found
220
221 call c%case%params%get('case.restart_file', restart_file, found)
222 call c%case%params%get('case.restart_mesh_file', restart_mesh_file, found)
223
224 if (found) then
225 call previous_meshf%init(trim(restart_mesh_file))
226 call previous_meshf%read(c%fluid_adj%chkp%previous_mesh)
227 end if
228
229 call c%case%params%get('case.mesh2mesh_tolerance', tol, found)
230
231 if (found) c%case%fluid%chkp%mesh2mesh_tol = tol
232
233 call chkpf%init(trim(restart_file))
234 call chkpf%read(c%fluid_adj%chkp)
235 c%time%dtlag = c%fluid_adj%chkp%dtlag
236 c%time%tlag = c%fluid_adj%chkp%tlag
237
238 ! Free the previous mesh, dont need it anymore
239 do i = 1, size(c%time%dtlag)
240 call c%case%fluid%ext_bdf%set_coeffs(c%time%dtlag)
241 end do
242
243 call c%fluid_adj%restart(c%case%chkp)
244 call c%case%fluid%chkp%previous_mesh%free()
245 if (allocated(c%adjoint_scalars)) then
246 call c%adjoint_scalars%restart(c%case%chkp)
247 end if
248
249 c%time%t = real(c%case%fluid%chkp%restart_time(), kind=rp)
250 call neko_log%section('Restarting from checkpoint')
251 write(log_buf, '(A,A)') 'File : ', trim(restart_file)
252 call neko_log%message(log_buf)
253 write(log_buf, '(A,E15.7)') 'Time : ', c%time%t
254 call neko_log%message(log_buf)
255 call neko_log%end_section()
256
257 call c%output_controller%set_counter(c%time)
258 end subroutine simulation_adjoint_restart
259
261 subroutine simulation_adjoint_joblimit_chkp(C, t)
262 type(adjoint_case_t), intent(inout) :: c
263 real(kind=rp), intent(inout) :: t
264 type(file_t) :: chkpf
265 character(len=:), allocatable :: chkp_format
266 character(len=LOG_SIZE) :: log_buf
267 character(len=10) :: format_str
268 logical :: found
269
270 call c%case%params%get('case.checkpoint_format', chkp_format, found)
271 call c%case%fluid%chkp%sync_host()
272 format_str = '.chkp'
273 if (found) then
274 if (chkp_format .eq. 'hdf5') then
275 format_str = '.h5'
276 end if
277 end if
278 call chkpf%init(c%case%output_directory // 'joblimit' // trim(format_str))
279 call chkpf%write(c%case%fluid%chkp, t)
280 write(log_buf, '(A)') '! saving checkpoint >>>'
281 call neko_log%message(log_buf)
282
283 end subroutine simulation_adjoint_joblimit_chkp
284
285end module simulation_adjoint
Adjoint simulation driver.
Adjoint case type. Todo: This should Ideally be a subclass of case_t, however, that is not yet suppor...