Skip to content

Commit 2e3017a

Browse files
Diego VacaDiego Vaca
authored andcommitted
Addressing comments 2
1 parent 1a4d597 commit 2e3017a

File tree

5 files changed

+25
-11
lines changed

5 files changed

+25
-11
lines changed

src/common/m_constants.fpp

Lines changed: 8 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -53,7 +53,14 @@ module m_constants
5353
! Strang Splitting constants
5454
real(wp), parameter :: dflt_adap_dt_tol = 1e-4_wp !< Default tolerance for adaptive step size
5555
integer, parameter :: adap_dt_max_iters = 100 !< Maximum number of iterations
56-
56+
! Constants of the algorithm described by Heirer, E. Hairer S.P.Nørsett G. Wanner, Solving Ordinary Differential Equations I, Chapter II.4
57+
! to choose the initial time step size for the adaptive time stepping routine
58+
real(wp), parameter :: threshold_first_guess = 1e-5_wp
59+
real(wp), parameter :: threshold_second_guess = 1e-15_wp
60+
real(wp), parameter :: scale_first_guess = 1e-3_wp
61+
real(wp), parameter :: scale_guess = 1e-2_wp
62+
real(wp), parameter :: small_guess = 1e-6_wp
63+
5764
! Relativity
5865
integer, parameter :: relativity_cons_to_prim_max_iter = 100
5966

src/simulation/m_bubbles.fpp

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -612,10 +612,10 @@ contains
612612
! Compute d_0 = ||y0|| and d_1 = ||f(x0,y0)||
613613
d_norms(1) = sqrt((myR_tmp(1)**2._wp + myV_tmp(1)**2._wp)/2._wp)
614614
d_norms(2) = sqrt((myV_tmp(1)**2._wp + myA_tmp(1)**2._wp)/2._wp)
615-
if (d_norms(1) < 1e-5_wp .or. d_norms(2) < 1e-5_wp) then
616-
h_size(1) = 1e-6_wp
615+
if (d_norms(1) < threshold_first_guess .or. d_norms(2) < threshold_first_guess) then
616+
h_size(1) = small_guess
617617
else
618-
h_size(1) = 1e-2_wp*(d_norms(1)/d_norms(2))
618+
h_size(1) = scale_guess*(d_norms(1)/d_norms(2))
619619
end if
620620

621621
! Evaluate f(x0+h0,y0+h0*f(x0,y0))
@@ -631,13 +631,13 @@ contains
631631

632632
! Set h1 = (0.01/max(d_1,d_2))^{1/(p+1)}
633633
! if max(d_1,d_2) < 1e-15_wp, h_size(2) = max(1e-6_wp, h0*1e-3_wp)
634-
if (max(d_norms(2), d_norms(3)) < 1e-15_wp) then
635-
h_size(2) = max(1e-6_wp, h_size(1)*1e-3_wp)
634+
if (max(d_norms(2), d_norms(3)) < threshold_second_guess) then
635+
h_size(2) = max(small_guess, h_size(1)*scale_first_guess)
636636
else
637-
h_size(2) = (1e-2_wp/max(d_norms(2), d_norms(3)))**(1._wp/3._wp)
637+
h_size(2) = (scale_guess/max(d_norms(2), d_norms(3)))**(1._wp/3._wp)
638638
end if
639639

640-
f_initial_substep_h = min(100._wp*h_size(1), h_size(2))
640+
f_initial_substep_h = min(h_size(1)/scale_guess, h_size(2))
641641

642642
end function f_initial_substep_h
643643

src/simulation/m_bubbles_EE.fpp

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -282,14 +282,16 @@ contains
282282
end if
283283

284284
! Adaptive time stepping
285+
adap_dt_stop = 0
286+
285287
if (adap_dt) then
286288

287289
call s_advance_step(myRho, myP, myR, myV, R0(q), &
288290
pb, pbdot, alf, n_tait, B_tait, &
289291
bub_adv_src(j, k, l), divu%sf(j, k, l), &
290292
dmBub_id, dmMass_v, dmMass_n, dmBeta_c, &
291293
dmBeta_t, dmCson, adap_dt_stop)
292-
adap_dt_stop_max = max(adap_dt_stop_max, adap_dt_stop)
294+
293295
q_cons_vf(rs(q))%sf(j, k, l) = nbub*myR
294296
q_cons_vf(vs(q))%sf(j, k, l) = nbub*myV
295297

@@ -302,6 +304,8 @@ contains
302304
bub_r_src(j, k, l, q) = q_cons_vf(vs(q))%sf(j, k, l)
303305
end if
304306

307+
adap_dt_stop_max = max(adap_dt_stop_max, adap_dt_stop)
308+
305309
if (alf < 1.e-11_wp) then
306310
bub_adv_src(j, k, l) = 0._wp
307311
bub_r_src(j, k, l, q) = 0._wp

src/simulation/m_bubbles_EL.fpp

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -572,13 +572,14 @@ contains
572572
call s_compute_cson_from_pinf(k, q_prim_vf, myPinf, cell, myRho, gamma, pi_inf, myCson)
573573

574574
! Adaptive time stepping
575+
adap_dt_stop = 0
576+
575577
if (adap_dt) then
576578

577579
call s_advance_step(myRho, myPinf, myR, myV, myR0, myPb, myPbdot, dmalf, &
578580
dmntait, dmBtait, dm_bub_adv_src, dm_divu, &
579581
k, myMass_v, myMass_n, myBeta_c, &
580582
myBeta_t, myCson, adap_dt_stop)
581-
adap_dt_stop_max = max(adap_dt_stop_max, adap_dt_stop)
582583

583584
! Update bubble state
584585
intfc_rad(k, 1) = myR
@@ -599,6 +600,8 @@ contains
599600

600601
end if
601602

603+
adap_dt_stop_max = max(adap_dt_stop_max, adap_dt_stop)
604+
602605
end do
603606

604607
if (adap_dt .and. adap_dt_stop_max > 0) stop "Adaptive time stepping failed to converge"

src/simulation/m_checker.fpp

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -115,7 +115,7 @@ contains
115115
if (.not. cfl_dt) then
116116
@:PROHIBIT(dt <= 0)
117117
end if
118-
@:PROHIBIT(time_stepper < 1 .or. time_stepper > 4)
118+
@:PROHIBIT(time_stepper < 1 .or. time_stepper > 3)
119119
end subroutine s_check_inputs_time_stepping
120120

121121
!> Checks constraints on parameters related to 6-equation model

0 commit comments

Comments
 (0)