Loading [MathJax]/extensions/tex2jax.js
Neko 0.9.1
A portable framework for high-order spectral element flow simulations
All Classes Namespaces Files Functions Variables Typedefs Enumerator Macros Pages
time_step_controller.f90
Go to the documentation of this file.
1! Copyright (c) 2022, 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
36 use logger, only : neko_log, log_size
37 use json_module, only : json_file
39 implicit none
40 private
41
43 type, public :: time_step_controller_t
45 logical :: if_variable_dt
46 real(kind=rp) :: set_cfl
47 real(kind=rp) :: max_dt
48 integer :: max_update_frequency
49 integer :: dt_last_change
50 real(kind=rp) :: alpha !coefficient of running average
51 real(kind=rp) :: max_dt_increase_factor, min_dt_decrease_factor
52 contains
54 procedure, pass(this) :: init => time_step_controller_init
56 procedure, pass(this) :: set_dt => time_step_controller_set_dt
57
59
60contains
61
64 subroutine time_step_controller_init(this, params)
65 class(time_step_controller_t), intent(inout) :: this
66 type(json_file), intent(inout) :: params
67
68 this%dt_last_change = 0
69 call json_get_or_default(params, 'case.variable_timestep',&
70 this%if_variable_dt, .false.)
71 call json_get_or_default(params, 'case.target_cfl',&
72 this%set_cfl, 0.4_rp)
73 call json_get_or_default(params, 'case.max_timestep',&
74 this%max_dt, huge(0.0_rp))
75 call json_get_or_default(params, 'case.cfl_max_update_frequency',&
76 this%max_update_frequency, 0)
77 call json_get_or_default(params, 'case.cfl_running_avg_coeff',&
78 this%alpha, 0.5_rp)
79 call json_get_or_default(params, 'case.max_dt_increase_factor',&
80 this%max_dt_increase_factor, 1.2_rp)
81 call json_get_or_default(params, 'case.min_dt_decrease_factor',&
82 this%min_dt_decrease_factor, 0.5_rp)
83
84 end subroutine time_step_controller_init
85
94 subroutine time_step_controller_set_dt(this, dt, cfl, cfl_avrg, tstep)
95 implicit none
96 class(time_step_controller_t), intent(inout) :: this
97 real(kind=rp), intent(inout) :: dt
98 real(kind=rp), intent(in) :: cfl
99 real(kind=rp), intent(inout) :: cfl_avrg
100 real(kind=rp) :: dt_old, scaling_factor
101 character(len=LOG_SIZE) :: log_buf
102 integer, intent(in):: tstep
103
104 if (this%if_variable_dt .eqv. .true.) then
105 if (tstep .eq. 1) then
106 ! set the first dt for desired cfl
107 dt = min(this%set_cfl/cfl*dt, this%max_dt)
108 else
109 ! Calculate the average of cfl over the desired interval
110 cfl_avrg = this%alpha * cfl + (1-this%alpha) * cfl_avrg
111
112 if (abs(cfl_avrg - this%set_cfl) .ge. 0.2*this%set_cfl .and. &
113 this%dt_last_change .ge. this%max_update_frequency) then
114
115 if (this%set_cfl/cfl .ge. 1) then
116 ! increase of time step
117 scaling_factor = min(this%max_dt_increase_factor, this%set_cfl/cfl)
118 else
119 ! reduction of time step
120 scaling_factor = max(this%min_dt_decrease_factor, this%set_cfl/cfl)
121 end if
122
123 dt_old = dt
124 dt = scaling_factor * dt_old
125 dt = min(dt, this%max_dt)
126
127 write(log_buf, '(A,E15.7,1x,A,E15.7)') 'Avrg CFL:', cfl_avrg, &
128 'set_cfl:', this%set_cfl
129 call neko_log%message(log_buf)
130
131 write(log_buf, '(A,E15.7,1x,A,E15.7)') 'old dt:', dt_old, &
132 'new dt:', dt
133 call neko_log%message(log_buf)
134
135 this%dt_last_change = 0
136
137 else
138 this%dt_last_change = this%dt_last_change + 1
139 end if
140 end if
141
142 end if
143
144 end subroutine time_step_controller_set_dt
145
146
147
148
149end module time_step_controller
Retrieves a parameter by name or assigns a provided default value. In the latter case also adds the m...
Utilities for retrieving parameters from the case files.
Logging routines.
Definition log.f90:34
type(log_t), public neko_log
Global log stream.
Definition log.f90:65
integer, parameter, public log_size
Definition log.f90:42
integer, parameter, public rp
Global precision used in computations.
Definition num_types.f90:12
Implements type time_step_controller.
subroutine time_step_controller_init(this, params)
Constructor.
subroutine time_step_controller_set_dt(this, dt, cfl, cfl_avrg, tstep)
Set new dt based on cfl if requested.
#define max(a, b)
Definition tensor.cu:40