Skip to content

Commit 125f94c

Browse files
authored
Add O/Ne Phase Separation Option for Massive WD Crystallization (#611)
1 parent 58cc92b commit 125f94c

File tree

5 files changed

+152
-66
lines changed

5 files changed

+152
-66
lines changed

star/defaults/controls.defaults

Lines changed: 16 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -7274,14 +7274,27 @@
72747274
! do_phase_separation
72757275
! ~~~~~~~~~~~~~~~~~~~
72767276

7277-
! Phase separation upon crystallization in WD cores (currently only for C/O white dwarf cores)
7278-
! using the implementation of `Bauer (2023) <https://ui.adsabs.harvard.edu/abs/2023arXiv230310110B/abstract>`_
7279-
! with the phase diagram of `Blouin et al. (2021) <https://ui.adsabs.harvard.edu/abs/2021PhRvE.103d3204B>`_.
7277+
! Phase separation upon crystallization in WD cores
7278+
! using the implementation of `Bauer (2023) <https://ui.adsabs.harvard.edu/abs/2023arXiv230310110B/abstract>`_.
72807279

72817280
! ::
72827281

72837282
do_phase_separation = .false.
72847283

7284+
! phase_separation_option
7285+
! ~~~~~~~~~~~~~~~~~~~~~~~
7286+
7287+
! Choice of appropriate option for the WD core mixture:
7288+
7289+
! + ``'CO'`` : carbon-oxygen phase separation using the two-component
7290+
! phase diagram of `Blouin & Daligault (2021a) <https://ui.adsabs.harvard.edu/abs/2021PhRvE.103d3204B/abstract>`_.
7291+
! + ``'ONe'`` : oxygen-neon phase separation using the two-component
7292+
! phase diagram of `Blouin & Daligault (2021b) <https://ui.adsabs.harvard.edu/abs/2021ApJ...919...87B/abstract>`_.
7293+
7294+
! ::
7295+
7296+
phase_separation_option = 'CO'
7297+
72857298
! do_phase_separation_heating
72867299
! ~~~~~~~~~~~~~~~~~~~~~~~~~~~
72877300

star/private/ctrls_io.f90

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -314,6 +314,7 @@ module ctrls_io
314314

315315
! WD phase separation
316316
do_phase_separation, &
317+
phase_separation_option, &
317318
do_phase_separation_heating, &
318319
phase_separation_mixing_use_brunt, &
319320
phase_separation_no_diffusion, &
@@ -1777,6 +1778,7 @@ subroutine store_controls(s, ierr)
17771778

17781779
! WD phase separation
17791780
s% do_phase_separation = do_phase_separation
1781+
s% phase_separation_option = phase_separation_option
17801782
s% do_phase_separation_heating = do_phase_separation_heating
17811783
s% phase_separation_mixing_use_brunt = phase_separation_mixing_use_brunt
17821784
s% phase_separation_no_diffusion = phase_separation_no_diffusion
@@ -3392,6 +3394,7 @@ subroutine set_controls_for_writing(s, ierr)
33923394
diffusion_dt_limit = s% diffusion_dt_limit
33933395

33943396
do_phase_separation = s% do_phase_separation
3397+
phase_separation_option = s% phase_separation_option
33953398
do_phase_separation_heating = s% do_phase_separation_heating
33963399
phase_separation_mixing_use_brunt = s% phase_separation_mixing_use_brunt
33973400
phase_separation_no_diffusion = s% phase_separation_no_diffusion

star/private/phase_separation.f90

Lines changed: 128 additions & 62 deletions
Original file line numberDiff line numberDiff line change
@@ -31,41 +31,56 @@ module phase_separation
3131

3232
implicit none
3333

34-
private
35-
public :: do_phase_separation
36-
3734
logical, parameter :: dbg = .false.
3835

3936
! offset to higher phase than 0.5 to avoid interference
4037
! between phase separation mixing and latent heat for Skye.
4138
real(dp), parameter :: eos_phase_boundary = 0.9d0
4239

43-
contains
40+
private
41+
public :: do_phase_separation
4442

43+
contains
4544

4645
subroutine do_phase_separation(s, dt, ierr)
47-
use chem_def, only: chem_isos, ic12, io16
46+
type (star_info), pointer :: s
47+
real(dp), intent(in) :: dt
48+
integer, intent(out) :: ierr
49+
50+
if(s% phase_separation_option == 'CO') then
51+
call do_2component_phase_separation(s, dt, 'CO', ierr)
52+
else if(s% phase_separation_option == 'ONe') then
53+
call do_2component_phase_separation(s, dt, 'ONe', ierr)
54+
else
55+
write(*,*) 'invalid phase_separation_option'
56+
stop
57+
end if
58+
end subroutine do_phase_separation
59+
60+
subroutine do_2component_phase_separation(s, dt, components, ierr)
61+
use chem_def, only: chem_isos, ic12, io16, ine20
4862
use chem_lib, only: chem_get_iso_id
4963
type (star_info), pointer :: s
5064
real(dp), intent(in) :: dt
65+
character (len=*), intent(in) :: components
5166
integer, intent(out) :: ierr
5267

53-
real(dp) :: dq_crystal, XO, XC, pad
54-
integer :: k, k_bound, kstart, net_ic12, net_io16
68+
real(dp) :: XNe, XO, XC, pad
69+
integer :: k, k_bound, kstart, net_ic12, net_io16, net_ine20
5570
logical :: save_Skye_use_ion_offsets
5671

72+
! Set phase separation mixing mass negative at beginning of phase separation
73+
s% phase_sep_mixing_mass = -1d0
5774
s% eps_phase_separation(1:s%nz) = 0d0
5875

5976
if(s% phase(s% nz) < eos_phase_boundary) then
6077
s% crystal_core_boundary_mass = 0d0
6178
return
6279
end if
63-
64-
! Set phase separation mixing mass negative at beginning of phase separation
65-
s% phase_sep_mixing_mass = -1d0
66-
80+
6781
net_ic12 = s% net_iso(ic12)
6882
net_io16 = s% net_iso(io16)
83+
net_ine20 = s% net_iso(ine20)
6984

7085
! Find zone of phase transition from liquid to solid
7186
k_bound = -1
@@ -75,15 +90,17 @@ subroutine do_phase_separation(s, dt, ierr)
7590
exit
7691
end if
7792
end do
78-
79-
! Check that we're still in C/O dominated material, otherwise skip phase separation
80-
XO = s% xa(net_io16,k_bound)
93+
8194
XC = s% xa(net_ic12,k_bound)
82-
if (XO + XC < 0.9d0) return
95+
XO = s% xa(net_io16,k_bound)
96+
XNe = s% xa(net_ine20,k_bound)
97+
! Check that we're still in C/O or O/Ne dominated material as appropriate,
98+
! otherwise skip phase separation
99+
if(components == 'CO'.and. XO + XC < 0.9d0) return
100+
if(components == 'ONe'.and. XNe + XO < 0.8d0) return ! O/Ne mixtures tend to have more byproducts of burning mixed in
83101

84102
! If there is a phase transition, reset the composition at the boundary
85103
if(k_bound > 0) then
86-
dq_crystal = 0d0
87104

88105
! core boundary needs to be padded by a minimal amount (less than a zone worth of mass)
89106
! to account for loss of precision during remeshing.
@@ -112,17 +129,15 @@ subroutine do_phase_separation(s, dt, ierr)
112129
exit
113130
end if
114131

115-
call move_one_zone(s,k,dq_crystal)
132+
call move_one_zone(s,k,components)
116133
! crystallized out to k now, liquid starts at k-1.
117134
! now mix the liquid material outward until stably stratified
118-
if(dq_crystal > 0d0) then
119-
call mix_outward(s, k-1)
120-
end if
135+
call mix_outward(s, k-1, 0)
121136

122137
end do
123138

124139
call update_model_(s,1,s%nz,.false.)
125-
140+
126141
! phase separation heating term for use by energy equation
127142
do k=1,s% nz
128143
s% eps_phase_separation(k) = (s% eps_phase_separation(k) - s% energy(k)) / dt
@@ -132,66 +147,86 @@ subroutine do_phase_separation(s, dt, ierr)
132147
end if
133148

134149
ierr = 0
135-
end subroutine do_phase_separation
150+
end subroutine do_2component_phase_separation
136151

137-
subroutine move_one_zone(s,k,dq_crystal)
138-
use chem_def, only: chem_isos, ic12, io16
152+
subroutine move_one_zone(s,k,components)
153+
use chem_def, only: chem_isos, ic12, io16, ine20
139154
use chem_lib, only: chem_get_iso_id
140155
type(star_info), pointer :: s
141156
integer, intent(in) :: k
142-
real(dp), intent(inout) :: dq_crystal
157+
character (len=*), intent(in) :: components
143158

144-
real(dp) :: XC, XO, XC1, XO1, dXO, Xfac, dqsum
145-
integer :: net_ic12, net_io16
146-
147-
dq_crystal = dq_crystal + s% dq(k)
159+
real(dp) :: XC, XO, XNe, XC1, XO1, XNe1, dXO, dXNe, Xfac
160+
integer :: net_ic12, net_io16, net_ine20
148161

149162
net_ic12 = s% net_iso(ic12)
150163
net_io16 = s% net_iso(io16)
164+
net_ine20 = s% net_iso(ine20)
151165

152-
XO = s% xa(net_io16,k)
153-
XC = s% xa(net_ic12,k)
166+
if(components == 'CO') then
167+
XO = s% xa(net_io16,k)
168+
XC = s% xa(net_ic12,k)
154169

155-
! Call Blouin 2021 phase diagram.
156-
! Need to rescale temporarily because phase diagram assumes XO + XC = 1
157-
Xfac = XO + XC
158-
XO = XO/Xfac
159-
XC = XC/Xfac
160-
161-
dXO = blouin_delta_xo(XO)
162-
163-
s% xa(net_io16,k) = Xfac*(XO + dXO)
164-
s% xa(net_ic12,k) = Xfac*(XC - dXO)
170+
! Call Blouin phase diagram.
171+
! Need to rescale temporarily because phase diagram assumes XO + XC = 1
172+
Xfac = XO + XC
173+
XO = XO/Xfac
174+
XC = XC/Xfac
175+
176+
dXO = blouin_delta_xo(XO)
177+
178+
s% xa(net_io16,k) = Xfac*(XO + dXO)
179+
s% xa(net_ic12,k) = Xfac*(XC - dXO)
180+
181+
! Redistribute change in C,O into zone k-1,
182+
! conserving total mass of C,O
183+
XC1 = s% xa(net_ic12,k-1)
184+
XO1 = s% xa(net_io16,k-1)
185+
s% xa(net_ic12,k-1) = XC1 + Xfac*dXO * s% dq(k) / s% dq(k-1)
186+
s% xa(net_io16,k-1) = XO1 - Xfac*dXO * s% dq(k) / s% dq(k-1)
187+
else if(components == 'ONe') then
188+
XNe = s% xa(net_ine20,k)
189+
XO = s% xa(net_io16,k)
165190

166-
! Redistribute change in X,O into zone k-1,
167-
! conserving total mass of X,O
168-
XC1 = s% xa(net_ic12,k-1)
169-
XO1 = s% xa(net_io16,k-1)
170-
s% xa(net_ic12,k-1) = XC1 + Xfac*dXO * s% dq(k) / s% dq(k-1)
171-
s% xa(net_io16,k-1) = XO1 - Xfac*dXO * s% dq(k) / s% dq(k-1)
191+
! Call Blouin phase diagram.
192+
! Need to rescale temporarily because phase diagram assumes XO + XNe = 1
193+
Xfac = XO + XNe
194+
XO = XO/Xfac
195+
XNe = XNe/Xfac
196+
197+
dXNe = blouin_delta_xne(XNe)
198+
199+
s% xa(net_ine20,k) = Xfac*(XNe + dXNe)
200+
s% xa(net_io16,k) = Xfac*(XO - dXNe)
201+
202+
! Redistribute change in Ne,O into zone k-1,
203+
! conserving total mass of Ne,O
204+
XO1 = s% xa(net_io16,k-1)
205+
XNe1 = s% xa(net_ine20,k-1)
206+
s% xa(net_io16,k-1) = XO1 + Xfac*dXNe * s% dq(k) / s% dq(k-1)
207+
s% xa(net_ine20,k-1) = XNe1 - Xfac*dXNe * s% dq(k) / s% dq(k-1)
208+
else
209+
write(*,*) 'invalid components option in phase separation'
210+
stop
211+
end if
172212

173213
call update_model_(s,k-1,s%nz,.true.)
174214

175215
end subroutine move_one_zone
176-
177-
! mix composition outward until reaching stable composition profile
178-
subroutine mix_outward(s,kbot)
179-
use chem_def, only: chem_isos, ihe4, ic12, io16
180216

217+
! mix composition outward until reaching stable composition profile
218+
subroutine mix_outward(s,kbot,min_mix_zones)
181219
type(star_info), pointer :: s
182-
integer, intent(in) :: kbot
220+
integer, intent(in) :: kbot, min_mix_zones
183221

184222
real(dp) :: avg_xa(s%species)
185-
real(dp) :: mass, dXC_top, dXC_bot, dXO_top, dXO_bot, B_term, grada, gradr
186-
integer :: k, l, ktop, net_ihe4, net_ic12, net_io16
223+
real(dp) :: mass, B_term, grada, gradr
224+
integer :: k, l, ktop
187225
logical :: use_brunt
188226

189227
use_brunt = s% phase_separation_mixing_use_brunt
190-
net_ihe4 = s% net_iso(ihe4)
191-
net_ic12 = s% net_iso(ic12)
192-
net_io16 = s% net_iso(io16)
193228

194-
do k=kbot,1,-1
229+
do k=kbot-min_mix_zones,1,-1
195230
ktop = k
196231

197232
if (s% m(ktop) > s% phase_sep_mixing_mass) then
@@ -234,7 +269,7 @@ subroutine mix_outward(s,kbot)
234269
end do
235270

236271
! Call a final update over all mixed cells now.
237-
call update_model_(s, ktop, kbot, .true.)
272+
call update_model_(s, ktop, kbot+1, .true.)
238273

239274
end subroutine mix_outward
240275

@@ -269,7 +304,39 @@ real(dp) function blouin_delta_xo(Xin)
269304

270305
blouin_delta_xo = Xnew - Xin
271306
end function blouin_delta_xo
272-
307+
308+
real(dp) function blouin_delta_xne(Xin)
309+
real(dp), intent(in) :: Xin ! mass fraction
310+
real(dp) :: Xnew ! mass fraction
311+
real(dp) :: xne, dxne ! number fractions
312+
real(dp) :: a0, a1, a2, a3, a4, a5
313+
314+
! Convert input mass fraction to number fraction, assuming O/Ne mixture
315+
xne = (Xin/20d0)/(Xin/20d0 + (1d0 - Xin)/16d0)
316+
317+
a0 = 0d0
318+
a1 = -0.120299d0
319+
a2 = 1.304399d0
320+
a3 = -1.722625d0
321+
a4 = 0.393996d0
322+
a5 = 0.144529d0
323+
324+
dxne = &
325+
a0 + &
326+
a1*xne + &
327+
a2*xne*xne + &
328+
a3*xne*xne*xne + &
329+
a4*xne*xne*xne*xne + &
330+
a5*xne*xne*xne*xne*xne
331+
332+
xne = xne + dxne
333+
334+
! Convert back to mass fraction
335+
Xnew = 20d0*xne/(20d0*xne + 16d0*(1d0-xne))
336+
337+
blouin_delta_xne = Xnew - Xin
338+
end function blouin_delta_xne
339+
273340
subroutine update_model_ (s, kc_t, kc_b, do_brunt)
274341

275342
use turb_info, only: set_mlt_vars
@@ -338,8 +405,7 @@ subroutine update_model_ (s, kc_t, kc_b, do_brunt)
338405
return
339406

340407
end subroutine update_model_
341-
342-
408+
343409
end module phase_separation
344410

345411

star/private/turb_info.f90

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -98,6 +98,7 @@ subroutine do1_mlt_2(s, k, &
9898
real(dp), pointer :: vel(:)
9999
integer :: i, mixing_type, h1, nz, k_T_max
100100
real(dp), parameter :: conv_vel_mach_limit = 0.9d0
101+
real(dp) :: crystal_pad
101102
logical :: no_mix
102103
type(auto_diff_real_star_order1) :: &
103104
grada_face_ad, scale_height_ad, gradr_ad, rho_face_ad, &
@@ -150,7 +151,9 @@ subroutine do1_mlt_2(s, k, &
150151
return
151152
end if
152153

153-
if (s% phase(k) > 0.5d0 .and. s% mu(k) > 1.7d0) then
154+
crystal_pad = s% min_dq * s% m(1) * 0.5d0
155+
if ((s% phase(k) > 0.5d0 .and. s% mu(k) > 1.7d0) &
156+
.or. s% crystal_core_boundary_mass + crystal_pad > s% m(k)) then
154157
! mu(k) check is so that we only evaluate this in C/O dominated material or heavier.
155158
! Helium can return bad phase info on Skye, so we don't want it to shut off
156159
! convection because of wrong phase information.

star_data/private/star_controls.inc

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1079,6 +1079,7 @@
10791079
logical :: do_phase_separation
10801080
logical :: do_phase_separation_heating
10811081
logical :: phase_separation_mixing_use_brunt
1082+
character (len=32) :: phase_separation_option
10821083

10831084
! timestep parameters
10841085

0 commit comments

Comments
 (0)