Line data Source code
1 : module eos_support
2 :
3 : use eos_def
4 : use eos_lib
5 : use const_def
6 : use chem_def
7 : use math_lib
8 : use utils_lib, only: is_bad_num
9 :
10 : implicit none
11 :
12 : logical, parameter :: use_shared_data_dir = .true. ! MUST BE .true. FOR RELEASE
13 : !logical, parameter :: use_shared_data_dir = .false.
14 :
15 : real(dp) :: X, Z, Zinit, Y, dXC, dXO, XC, XO, abar, zbar, z2bar, z53bar, ye
16 : integer, parameter :: species = 7
17 : integer, parameter :: h1 = 1, he4 = 2, c12 = 3, n14 = 4, o16 = 5, ne20 = 6, mg24 = 7
18 : integer, target :: chem_id_array(species)
19 : integer, pointer, dimension(:) :: chem_id, net_iso
20 : real(dp) :: xa(species)
21 :
22 : real(dp), allocatable :: d_dxa(:, :) ! (num_d_dxa_basic_results,species)
23 :
24 : integer :: handle
25 : type(EoS_General_Info), pointer :: rq
26 :
27 : character(len=eos_name_length) :: eos_names(num_eos_basic_results)
28 :
29 : ! if false, then test using data from mesa/eos/data/eos_data
30 : ! if true, then test using data from mesa/data/eos_data
31 :
32 : contains
33 :
34 18 : subroutine Init_Composition(X_in, Zinit_in, XC_in, XO_in)
35 : use chem_lib
36 : real(dp), intent(IN) :: X_in, Zinit_in, XC_in, XO_in
37 :
38 : real(dp), parameter :: Zfrac_C = 0.173312d0
39 : real(dp), parameter :: Zfrac_N = 0.053177d0
40 : real(dp), parameter :: Zfrac_O = 0.482398d0
41 : real(dp), parameter :: Zfrac_Ne = 0.098675d0
42 :
43 : real(dp) :: Z, frac, dabar_dx(species), dzbar_dx(species), sumx, &
44 : mass_correction, dmc_dx(species)
45 :
46 18 : chem_id => chem_id_array
47 :
48 18 : allocate (net_iso(num_chem_isos))
49 141426 : net_iso(:) = 0
50 :
51 18 : chem_id(h1) = ih1; net_iso(ih1) = h1
52 18 : chem_id(he4) = ihe4; net_iso(ihe4) = he4
53 18 : chem_id(c12) = ic12; net_iso(ic12) = c12
54 18 : chem_id(n14) = in14; net_iso(in14) = n14
55 18 : chem_id(o16) = io16; net_iso(io16) = o16
56 18 : chem_id(ne20) = ine20; net_iso(ine20) = ne20
57 18 : chem_id(mg24) = img24; net_iso(img24) = mg24
58 :
59 18 : X = X_in
60 18 : Zinit = Zinit_in
61 18 : XC = XC_in; XO = XO_in
62 18 : Y = 1 - (X + Zinit + XC + XO)
63 18 : if (Y < 0) then ! adjust XC and XO
64 0 : if (XC + XO <= 0) then
65 0 : write (*, *) 'bad args to Init_Composition'
66 0 : call mesa_error(__FILE__, __LINE__)
67 : end if
68 0 : frac = (1 - X - Zinit)/(XC + XO)
69 0 : if (frac <= 0) call mesa_error(__FILE__, __LINE__, 'bad args to Init_Composition')
70 0 : XC = frac*XC; XO = frac*XO
71 0 : Y = 1 - (X + Zinit + XC + XO)
72 0 : if (Y < -1d-10) then
73 0 : write (*, *) 'screw up in Init_Composition'
74 0 : call mesa_error(__FILE__, __LINE__)
75 : end if
76 0 : if (Y < 0) Y = 0
77 : end if
78 :
79 18 : xa(h1) = X
80 18 : xa(he4) = Y
81 18 : xa(c12) = Zinit*Zfrac_C + XC
82 18 : xa(n14) = Zinit*Zfrac_N
83 18 : xa(o16) = Zinit*Zfrac_O + XO
84 18 : xa(ne20) = Zinit*Zfrac_Ne
85 126 : xa(species) = 1 - sum(xa(1:species - 1))
86 :
87 : call composition_info( &
88 : species, chem_id, xa, X, Y, Z, abar, zbar, z2bar, z53bar, &
89 18 : ye, mass_correction, sumx, dabar_dx, dzbar_dx, dmc_dx)
90 :
91 18 : end subroutine Init_Composition
92 :
93 1 : subroutine Setup_eos
94 18 : use chem_lib
95 : use const_lib, only: const_init
96 : !..allocate and load the eos tables
97 :
98 : character(len=256) :: my_mesa_dir
99 : integer :: info
100 : logical :: use_cache
101 :
102 1 : info = 0
103 1 : allocate (d_dxa(num_eos_d_dxa_results, species), stat=info)
104 1 : if (info /= 0) then
105 0 : write (*, *) 'allocate failed for Setup_eos'
106 0 : call mesa_error(__FILE__, __LINE__)
107 : end if
108 :
109 1 : my_mesa_dir = '../..'
110 1 : call const_init(my_mesa_dir, info)
111 1 : if (info /= 0) then
112 0 : write (*, *) 'const_init failed'
113 0 : call mesa_error(__FILE__, __LINE__)
114 : end if
115 :
116 1 : call math_init()
117 :
118 1 : call chem_init('isotopes.data', info)
119 1 : if (info /= 0) then
120 0 : write (*, *) 'chem_init failed'
121 0 : call mesa_error(__FILE__, __LINE__)
122 : end if
123 :
124 1 : use_cache = .true.
125 :
126 1 : call eos_init(' ', use_cache, info)
127 1 : if (info /= 0) then
128 0 : write (*, *) 'failed in eos_init'
129 0 : call mesa_error(__FILE__, __LINE__)
130 : end if
131 27 : eos_names = eosDT_result_names
132 :
133 1 : handle = alloc_eos_handle_using_inlist('inlist', info)
134 1 : if (info /= 0) then
135 0 : write (*, *) 'failed in alloc_eos_handle_using_inlist'
136 0 : call mesa_error(__FILE__, __LINE__)
137 : end if
138 :
139 1 : call eos_ptr(handle, rq, info)
140 1 : if (info /= 0) then
141 0 : write (*, *) 'failed in eos_ptr'
142 0 : call mesa_error(__FILE__, __LINE__)
143 : end if
144 :
145 5 : end subroutine Setup_eos
146 :
147 0 : subroutine Shutdown_eos
148 0 : call free_eos_handle(handle)
149 0 : call eos_shutdown
150 0 : deallocate (d_dxa)
151 1 : end subroutine Shutdown_eos
152 :
153 : end module eos_support
|