Skip to content

Commit 54acecf

Browse files
authored
WD CO Phase Separation Updates (#480)
* simplify phase separation EOS update interface * do phase separation EOS update at constant pressure * update Skye interface to make computing ion offsets optional * ignore ion offset energy when computing phase separation heating * simplify mixing procedure now that energetics are better
1 parent 152c8fd commit 54acecf

File tree

7 files changed

+65
-49
lines changed

7 files changed

+65
-49
lines changed

eos/defaults/eos.defaults

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -180,6 +180,14 @@
180180

181181
mass_fraction_limit_for_Skye = 1d-4
182182

183+
! Skye_use_ion_offsets
184+
! ~~~~~~~~~~~~~~~~~~~~
185+
! If true, set neutral ground state as zero point for each ion species energy.
186+
! If false, zero point assumes fully ionized.
187+
! ::
188+
189+
Skye_use_ion_offsets = .true.
190+
183191
! Skye Gamma Limits
184192
! ~~~~~~~~~~~~~~~~~
185193
! The one-component plasma fits in Skye are only valid in certain ranges of the ion interaction parameter Gamma.

eos/private/eos_ctrls_io.f90

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -106,6 +106,7 @@ module eos_ctrls_io
106106

107107
! limits for Skye
108108
logical :: use_Skye
109+
logical :: Skye_use_ion_offsets
109110
real(dp) :: mass_fraction_limit_for_Skye
110111
real(dp) :: Skye_min_gamma_for_solid ! The minimum Gamma_i at which to use the solid free energy fit (below this, extrapolate).
111112
real(dp) :: Skye_max_gamma_for_liquid ! The maximum Gamma_i at which to use the liquid free energy fit (above this, extrapolate).
@@ -231,6 +232,7 @@ module eos_ctrls_io
231232

232233
! controls for Skye
233234
use_Skye, &
235+
Skye_use_ion_offsets, &
234236
mass_fraction_limit_for_Skye, &
235237
Skye_min_gamma_for_solid, & ! The minimum Gamma_i at which to use the solid free energy fit (below this, extrapolate).
236238
Skye_max_gamma_for_liquid, & ! The maximum Gamma_i at which to use the liquid free energy fit (above this, extrapolate).
@@ -486,6 +488,7 @@ subroutine store_controls(rq)
486488
rq% PC_Gamma_full_crystal = PC_Gamma_full_crystal
487489
! controls for Skye
488490
rq% use_Skye = use_Skye
491+
rq% Skye_use_ion_offsets = Skye_use_ion_offsets
489492
rq% mass_fraction_limit_for_Skye = mass_fraction_limit_for_Skye
490493
rq%Skye_min_gamma_for_solid = Skye_min_gamma_for_solid
491494
rq%Skye_max_gamma_for_liquid = Skye_max_gamma_for_liquid
@@ -622,6 +625,7 @@ subroutine set_controls_for_writing(rq)
622625
PC_Gamma_full_crystal = rq% PC_Gamma_full_crystal
623626
! controls for Skye
624627
use_Skye = rq% use_Skye
628+
Skye_use_ion_offsets = rq% Skye_use_ion_offsets
625629
mass_fraction_limit_for_Skye = rq% mass_fraction_limit_for_Skye
626630
Skye_min_gamma_for_solid = rq% Skye_min_gamma_for_solid
627631
Skye_max_gamma_for_liquid = rq% Skye_max_gamma_for_liquid

eos/private/skye.f90

Lines changed: 7 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -211,6 +211,7 @@ subroutine Get_Skye_EOS_Results( &
211211
T, Rho, X, abar, zbar, &
212212
rq%Skye_min_gamma_for_solid, rq%Skye_max_gamma_for_liquid, &
213213
rq%Skye_solid_mixing_rule, rq%mass_fraction_limit_for_Skye, &
214+
rq%Skye_use_ion_offsets, &
214215
species, chem_id, xa, &
215216
res, d_dlnd, d_dlnT, d_dxa, ierr)
216217

@@ -259,7 +260,8 @@ subroutine skye_eos( &
259260
temp_in, den_in, Xfrac, abar, zbar, &
260261
Skye_min_gamma_for_solid, Skye_max_gamma_for_liquid, &
261262
Skye_solid_mixing_rule, &
262-
mass_fraction_limit, species, chem_id, xa, &
263+
mass_fraction_limit, use_ion_offsets, &
264+
species, chem_id, xa, &
263265
res, d_dlnd, d_dlnT, d_dxa, ierr)
264266

265267
use eos_def
@@ -279,6 +281,7 @@ subroutine skye_eos( &
279281
real(dp), intent(in) :: xa(:)
280282
real(dp), intent(in) :: temp_in, den_in, mass_fraction_limit, Skye_min_gamma_for_solid, Skye_max_gamma_for_liquid
281283
real(dp), intent(in) :: Xfrac, abar, zbar
284+
logical, intent(in) :: use_ion_offsets
282285
character(len=128), intent(in) :: Skye_solid_mixing_rule
283286
integer, intent(out) :: ierr
284287
real(dp), intent(out), dimension(nv) :: res, d_dlnd, d_dlnT
@@ -351,7 +354,9 @@ subroutine skye_eos( &
351354
! Ideal ion free energy, only depends on abar
352355
F_ideal_ion = compute_F_ideal_ion(temp, den, abar, relevant_species, ACMI, ya)
353356

354-
F_ideal_ion = F_ideal_ion + compute_ion_offset(species, xa, chem_id) ! Offset so ion ground state energy is zero.
357+
if (use_ion_offsets) then
358+
F_ideal_ion = F_ideal_ion + compute_ion_offset(species, xa, chem_id) ! Offset so ion ground state energy is zero.
359+
end if
355360

356361
! Ideal electron-positron thermodynamics (s, e, p)
357362
! Derivatives are handled by HELM code, so we don't pass *in* any auto_diff types (just get them as return values).

eos/public/eos_def.f90

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -293,6 +293,7 @@ end subroutine other_eos_interface
293293

294294
! limits for Skye
295295
logical :: use_Skye
296+
logical :: Skye_use_ion_offsets
296297
real(dp) :: mass_fraction_limit_for_Skye
297298
real(dp) :: Skye_min_gamma_for_solid ! The minimum Gamma_i at which to use the solid free energy fit (below this, extrapolate).
298299
real(dp) :: Skye_max_gamma_for_liquid ! The maximum Gamma_i at which to use the liquid free energy fit (above this, extrapolate).

star/private/evolve.f90

Lines changed: 2 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -624,16 +624,11 @@ integer function do_step_part2(id, first_try)
624624
end if
625625

626626
if(s% do_phase_separation) then
627-
do k=1,s% nz
628-
s% eps_phase_separation(k) = s% energy(k)
629-
end do
630-
call do_phase_separation(s, ierr)
627+
call do_phase_separation(s, dt, ierr)
631628
if (failed('do_phase_separation')) return
629+
632630
call set_vars_if_needed(s, dt, 'after phase separation', ierr)
633631
if (failed('set_vars_if_needed after phase separation')) return
634-
do k=1,s% nz ! for use by energy equation
635-
s% eps_phase_separation(k) = (s% eps_phase_separation(k) - s% energy(k)) / dt
636-
end do
637632
else
638633
s% crystal_core_boundary_mass = -1d0
639634
end if

star/private/phase_separation.f90

Lines changed: 39 additions & 40 deletions
Original file line numberDiff line numberDiff line change
@@ -36,24 +36,25 @@ module phase_separation
3636

3737
logical, parameter :: dbg = .false.
3838

39-
integer, parameter :: FIXED_PT_MODE = 5
40-
integer, parameter :: FIXED_DT_MODE = 6
41-
4239
! offset to higher phase than 0.5 to avoid interference
4340
! between phase separation mixing and latent heat for Skye.
4441
real(dp), parameter :: eos_phase_boundary = 0.9d0
4542

4643
contains
4744

4845

49-
subroutine do_phase_separation(s, ierr)
46+
subroutine do_phase_separation(s, dt, ierr)
5047
use chem_def, only: chem_isos, ic12, io16
5148
use chem_lib, only: chem_get_iso_id
5249
type (star_info), pointer :: s
50+
real(dp), intent(in) :: dt
5351
integer, intent(out) :: ierr
5452

5553
real(dp) :: dq_crystal, XO, XC, pad
5654
integer :: k, k_bound, kstart, net_ic12, net_io16
55+
logical :: save_Skye_use_ion_offsets
56+
57+
s% eps_phase_separation(:) = 0d0
5758

5859
if(s% phase(s% nz) < eos_phase_boundary) then
5960
s% crystal_core_boundary_mass = 0d0
@@ -93,6 +94,15 @@ subroutine do_phase_separation(s, ierr)
9394
exit
9495
end if
9596
end do
97+
98+
! calculate energy associated with phase separation, ignoring the ionization
99+
! energy term that Skye sometimes calculates
100+
save_Skye_use_ion_offsets = s% eos_rq% Skye_use_ion_offsets
101+
s% eos_rq% Skye_use_ion_offsets = .false.
102+
call update_model_(s,1,s%nz,.false.)
103+
do k=1,s% nz
104+
s% eps_phase_separation(k) = s% energy(k)
105+
end do
96106

97107
! loop runs outward starting at previous crystallization boundary
98108
do k = kstart,1,-1
@@ -111,6 +121,13 @@ subroutine do_phase_separation(s, ierr)
111121

112122
end do
113123

124+
call update_model_(s,1,s%nz,.false.)
125+
126+
! phase separation heating term for use by energy equation
127+
do k=1,s% nz
128+
s% eps_phase_separation(k) = (s% eps_phase_separation(k) - s% energy(k)) / dt
129+
end do
130+
s% eos_rq% Skye_use_ion_offsets = save_Skye_use_ion_offsets
114131
s% need_to_setvars = .true.
115132
end if
116133

@@ -126,9 +143,6 @@ subroutine move_one_zone(s,k,dq_crystal)
126143

127144
real(dp) :: XC, XO, XC1, XO1, dXO, Xfac, dqsum
128145
integer :: net_ic12, net_io16
129-
integer :: update_mode(s%nz)
130-
131-
update_mode(:) = FIXED_DT_MODE
132146

133147
dq_crystal = dq_crystal + s% dq(k)
134148

@@ -156,7 +170,7 @@ subroutine move_one_zone(s,k,dq_crystal)
156170
s% xa(net_ic12,k-1) = XC1 + Xfac*dXO * s% dq(k) / s% dq(k-1)
157171
s% xa(net_io16,k-1) = XO1 - Xfac*dXO * s% dq(k) / s% dq(k-1)
158172

159-
call update_model_(s,update_mode,k-1,s%nz,.true.)
173+
call update_model_(s,k-1,s%nz,.true.)
160174

161175
end subroutine move_one_zone
162176

@@ -168,12 +182,10 @@ subroutine mix_outward(s,kbot)
168182
integer, intent(in) :: kbot
169183

170184
real(dp) :: avg_xa(s%species)
171-
real(dp) :: mass, XHe_out, dXC_top, dXC_bot, dXO_top, dXO_bot, B_term, grada, gradr
185+
real(dp) :: mass, dXC_top, dXC_bot, dXO_top, dXO_bot, B_term, grada, gradr
172186
integer :: k, l, ktop, net_ihe4, net_ic12, net_io16
173-
integer :: update_mode(s%nz)
174187
logical :: use_brunt
175188

176-
update_mode(:) = FIXED_DT_MODE
177189
use_brunt = s% phase_separation_mixing_use_brunt
178190
net_ihe4 = s% net_iso(ihe4)
179191
net_ic12 = s% net_iso(ic12)
@@ -195,32 +207,14 @@ subroutine mix_outward(s,kbot)
195207
! avg_xa = MAX(MIN(avg_xa, 1._dp), 0._dp)
196208
! avg_xa = avg_xa/SUM(avg_xa)
197209

198-
XHe_out = max(s%xa(net_ihe4,ktop),s%xa(net_ihe4,ktop-1))
199-
if(XHe_out < s% eos_rq% mass_fraction_limit_for_Skye) then
200-
! ok to mix all species
201-
do l = 1, s%species
202-
s%xa(l,ktop:kbot) = avg_xa(l)
203-
end do
204-
else
205-
! Mixing He can cause energy problems for eps_phase_separation
206-
! when using Skye, so once we encounter enough He that it is
207-
! included in Skye energy calculation, stop mixing all species.
208-
! Instead, just flatten out the O16 profile, and mix in exchange
209-
! for C12.
210-
dXO_top = avg_xa(net_io16) - s%xa(net_io16,ktop)
211-
dXO_bot = avg_xa(net_io16) - s%xa(net_io16,kbot)
212-
s%xa(net_io16,ktop:kbot) = avg_xa(net_io16)
213-
dXC_top = -dXO_top
214-
dXC_bot = -dXO_bot
215-
s%xa(net_ic12,ktop) = s%xa(net_ic12,ktop) + dXC_top
216-
s%xa(net_ic12,ktop+1:kbot) = s%xa(net_ic12,kbot) + dXC_bot
217-
end if
218-
210+
do l = 1, s%species
211+
s%xa(l,ktop:kbot) = avg_xa(l)
212+
end do
219213

220214
! updates, eos, opacities, mu, etc now that abundances have changed,
221215
! but only in the cells near the boundary where we need to check here.
222216
! Will call full update over mixed region after exiting loop.
223-
call update_model_(s, update_mode, ktop-1, ktop+1, use_brunt)
217+
call update_model_(s, ktop-1, ktop+1, use_brunt)
224218

225219
if(use_brunt) then
226220
B_term = s% unsmoothed_brunt_B(ktop)
@@ -240,7 +234,7 @@ subroutine mix_outward(s,kbot)
240234
end do
241235

242236
! Call a final update over all mixed cells now.
243-
call update_model_(s, update_mode, ktop, kbot, .true.)
237+
call update_model_(s, ktop, kbot, .true.)
244238

245239
end subroutine mix_outward
246240

@@ -276,30 +270,35 @@ real(dp) function blouin_delta_xo(Xin)
276270
blouin_delta_xo = Xnew - Xin
277271
end function blouin_delta_xo
278272

279-
subroutine update_model_ (s, update_mode, kc_t, kc_b, do_brunt)
273+
subroutine update_model_ (s, kc_t, kc_b, do_brunt)
280274

281275
use turb_info, only: set_mlt_vars
282276
use brunt, only: do_brunt_B
283277
use micro
284278

285279
type(star_info), pointer :: s
286-
integer, intent(in) :: update_mode(:)
287280
integer, intent(in) :: kc_t
288281
integer, intent(in) :: kc_b
289282
logical, intent(in) :: do_brunt
290283

291284
integer :: ierr
292285
integer :: kf_t
293286
integer :: kf_b
294-
287+
288+
logical :: mask(s%nz)
289+
290+
mask(:) = .true.
291+
295292
! Update the model to reflect changes in the abundances across
296-
! cells kc_t:kc_b
297-
298-
call set_eos_with_mask(s, kc_t, kc_b, update_mode==FIXED_DT_MODE, ierr)
293+
! cells kc_t:kc_b (the mask part of this call is unused, mask=true for all zones).
294+
! Do updates at constant (P,T) rather than constant (rho,T).
295+
s%fix_Pgas = .true.
296+
call set_eos_with_mask(s, kc_t, kc_b, mask, ierr)
299297
if (ierr /= 0) then
300298
write(*,*) 'phase_separation: error from call to set_eos_with_mask'
301299
stop
302300
end if
301+
s%fix_Pgas = .false.
303302

304303
! Update opacities across cells kc_t:kc_b (this also sets rho_face
305304
! and related quantities on faces kc_t:kc_b)

star/test_suite/wd_cool_0.6M/inlist_wd_cool_0.6M

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -69,6 +69,10 @@
6969
atm_option = 'table'
7070
atm_table = 'WD_tau_25'
7171

72+
! C/O phase separation
73+
! do_phase_separation = .true.
74+
! do_phase_separation_heating = .true.
75+
7276
! Diffusion controls
7377
do_element_diffusion = .true.
7478
diffusion_use_full_net = .true.

0 commit comments

Comments
 (0)