Line data Source code
1 : ! ***********************************************************************
2 : !
3 : ! Copyright (C) 2010 The MESA Team
4 : !
5 : ! This program is free software: you can redistribute it and/or modify
6 : ! it under the terms of the GNU Lesser General Public License
7 : ! as published by the Free Software Foundation,
8 : ! either version 3 of the License, or (at your option) any later version.
9 : !
10 : ! This program is distributed in the hope that it will be useful,
11 : ! but WITHOUT ANY WARRANTY; without even the implied warranty of
12 : ! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
13 : ! See the GNU Lesser General Public License for more details.
14 : !
15 : ! You should have received a copy of the GNU Lesser General Public License
16 : ! along with this program. If not, see <https://www.gnu.org/licenses/>.
17 : !
18 : ! ***********************************************************************
19 :
20 : module binary_private_def
21 :
22 : use binary_def
23 :
24 : implicit none
25 :
26 : ! history column options
27 :
28 : integer, parameter :: bh_model_number = 1
29 : integer, parameter :: bh_age = bh_model_number + 1
30 : integer, parameter :: bh_donor_index = bh_age + 1
31 : integer, parameter :: bh_period_days = bh_donor_index + 1
32 : integer, parameter :: bh_period_hr = bh_period_days + 1
33 : integer, parameter :: bh_period_minutes = bh_period_hr + 1
34 : integer, parameter :: bh_lg_separation = bh_period_minutes + 1
35 : integer, parameter :: bh_binary_separation = bh_lg_separation + 1
36 : integer, parameter :: bh_eccentricity = bh_binary_separation + 1
37 : integer, parameter :: bh_star_1_radius = bh_eccentricity + 1
38 : integer, parameter :: bh_star_2_radius = bh_star_1_radius + 1
39 : integer, parameter :: bh_rl_1 = bh_star_2_radius + 1
40 : integer, parameter :: bh_rl_2 = bh_rl_1 + 1
41 : integer, parameter :: bh_rl_overflow_1 = bh_rl_2 + 1
42 : integer, parameter :: bh_rl_overflow_2 = bh_rl_overflow_1 + 1
43 : integer, parameter :: bh_rl_relative_overflow_1 = bh_rl_overflow_2 + 1
44 : integer, parameter :: bh_rl_relative_overflow_2 = bh_rl_relative_overflow_1 + 1
45 : integer, parameter :: bh_P_rot_div_P_orb_1 = bh_rl_relative_overflow_2 + 1
46 : integer, parameter :: bh_P_rot_div_P_orb_2 = bh_P_rot_div_P_orb_1 + 1
47 : integer, parameter :: bh_lg_t_sync_1 = bh_P_rot_div_P_orb_2 + 1
48 : integer, parameter :: bh_lg_t_sync_2 = bh_lg_t_sync_1 + 1
49 : integer, parameter :: bh_star_1_mass = bh_lg_t_sync_2 + 1
50 : integer, parameter :: bh_lg_star_1_mass = bh_star_1_mass + 1
51 : integer, parameter :: bh_star_2_mass = bh_lg_star_1_mass + 1
52 : integer, parameter :: bh_lg_star_2_mass = bh_star_2_mass + 1
53 : integer, parameter :: bh_sum_of_masses = bh_lg_star_2_mass + 1
54 : integer, parameter :: bh_mass_ratio = bh_sum_of_masses + 1
55 : integer, parameter :: bh_obs_mass_ratio = bh_mass_ratio + 1
56 : integer, parameter :: bh_lg_mtransfer_rate = bh_obs_mass_ratio + 1
57 : integer, parameter :: bh_lg_mstar_dot_1 = bh_lg_mtransfer_rate + 1
58 : integer, parameter :: bh_lg_mstar_dot_2 = bh_lg_mstar_dot_1 + 1
59 : integer, parameter :: bh_lg_system_mdot_1 = bh_lg_mstar_dot_2 + 1
60 : integer, parameter :: bh_lg_system_mdot_2 = bh_lg_system_mdot_1 + 1
61 : integer, parameter :: bh_lg_wind_mdot_1 = bh_lg_system_mdot_2 + 1
62 : integer, parameter :: bh_lg_wind_mdot_2 = bh_lg_wind_mdot_1 + 1
63 : integer, parameter :: bh_star_1_div_star_2_mass = bh_lg_wind_mdot_2 + 1
64 : integer, parameter :: bh_delta_star_1_mass = bh_star_1_div_star_2_mass + 1
65 : integer, parameter :: bh_delta_star_2_mass = bh_delta_star_1_mass + 1
66 : integer, parameter :: bh_fixed_xfer_fraction = bh_delta_star_2_mass + 1
67 : integer, parameter :: bh_eff_xfer_fraction = bh_fixed_xfer_fraction + 1
68 : integer, parameter :: bh_lg_mdot_edd = bh_eff_xfer_fraction + 1
69 : integer, parameter :: bh_mdot_edd_eta = bh_lg_mdot_edd + 1
70 : integer, parameter :: bh_lg_accretion_luminosity = bh_mdot_edd_eta + 1
71 : integer, parameter :: bh_bh_spin = bh_lg_accretion_luminosity + 1
72 : integer, parameter :: bh_v_orb_1 = bh_bh_spin + 1
73 : integer, parameter :: bh_v_orb_2 = bh_v_orb_1 + 1
74 : integer, parameter :: bh_lg_F_irr = bh_v_orb_2 + 1
75 : integer, parameter :: bh_J_orb = bh_lg_F_irr + 1
76 : integer, parameter :: bh_J_spin_1 = bh_J_orb + 1
77 : integer, parameter :: bh_J_spin_2 = bh_J_spin_1 + 1
78 : integer, parameter :: bh_J_total = bh_J_spin_2 + 1
79 : integer, parameter :: bh_Jdot = bh_J_total + 1
80 : integer, parameter :: bh_jdot_mb = bh_Jdot + 1
81 : integer, parameter :: bh_jdot_gr = bh_jdot_mb + 1
82 : integer, parameter :: bh_jdot_ml = bh_jdot_gr + 1
83 : integer, parameter :: bh_jdot_ls = bh_jdot_ml + 1
84 : integer, parameter :: bh_jdot_missing_wind = bh_jdot_ls + 1
85 : integer, parameter :: bh_extra_jdot = bh_jdot_missing_wind + 1
86 : integer, parameter :: bh_accretion_mode = bh_extra_jdot + 1
87 : integer, parameter :: bh_acc_am_div_kep_am = bh_accretion_mode + 1
88 : integer, parameter :: bh_edot = bh_acc_am_div_kep_am + 1
89 : integer, parameter :: bh_edot_tidal = bh_edot + 1
90 : integer, parameter :: bh_edot_enhance = bh_edot_tidal + 1
91 : integer, parameter :: bh_extra_edot = bh_edot_enhance + 1
92 : integer, parameter :: bh_point_mass_index = bh_extra_edot + 1
93 : integer, parameter :: bh_ignore_rlof_flag = bh_point_mass_index + 1
94 : integer, parameter :: bh_model_twins_flag = bh_ignore_rlof_flag + 1
95 : integer, parameter :: bh_CE_flag = bh_model_twins_flag + 1
96 : integer, parameter :: bh_CE_lambda1 = bh_CE_flag + 1
97 : integer, parameter :: bh_CE_lambda2 = bh_CE_lambda1 + 1
98 : integer, parameter :: bh_CE_Ebind1 = bh_CE_lambda2 + 1
99 : integer, parameter :: bh_CE_Ebind2 = bh_CE_Ebind1 + 1
100 : integer, parameter :: bh_CE_num1 = bh_CE_Ebind2 + 1
101 : integer, parameter :: bh_CE_num2 = bh_CE_num1 + 1
102 :
103 : integer, parameter :: bh_col_id_max = bh_CE_num2
104 :
105 : character (len=maxlen_binary_history_column_name) :: binary_history_column_name(bh_col_id_max)
106 :
107 : contains
108 :
109 :
110 0 : subroutine binary_history_column_names_init(ierr)
111 : integer, intent(out) :: ierr
112 :
113 : integer :: i, cnt
114 0 : ierr = 0
115 0 : cnt = 0
116 0 : binary_history_column_name(:) = ''
117 :
118 0 : binary_history_column_name(bh_model_number) = 'model_number'
119 0 : binary_history_column_name(bh_age) = 'age'
120 0 : binary_history_column_name(bh_donor_index) = 'donor_index'
121 0 : binary_history_column_name(bh_period_days) = 'period_days'
122 0 : binary_history_column_name(bh_period_hr) = 'period_hr'
123 0 : binary_history_column_name(bh_period_minutes) = 'period_minutes'
124 0 : binary_history_column_name(bh_lg_separation) = 'lg_separation'
125 0 : binary_history_column_name(bh_binary_separation) = 'binary_separation'
126 0 : binary_history_column_name(bh_eccentricity) = 'eccentricity'
127 0 : binary_history_column_name(bh_star_1_radius) = 'star_1_radius'
128 0 : binary_history_column_name(bh_star_2_radius) = 'star_2_radius'
129 0 : binary_history_column_name(bh_rl_1) = 'rl_1'
130 0 : binary_history_column_name(bh_rl_2) = 'rl_2'
131 0 : binary_history_column_name(bh_rl_overflow_1) = 'rl_overflow_1'
132 0 : binary_history_column_name(bh_rl_overflow_2) = 'rl_overflow_2'
133 0 : binary_history_column_name(bh_rl_relative_overflow_1) = 'rl_relative_overflow_1'
134 0 : binary_history_column_name(bh_rl_relative_overflow_2) = 'rl_relative_overflow_2'
135 0 : binary_history_column_name(bh_P_rot_div_P_orb_1) = 'P_rot_div_P_orb_1'
136 0 : binary_history_column_name(bh_P_rot_div_P_orb_2) = 'P_rot_div_P_orb_2'
137 0 : binary_history_column_name(bh_lg_t_sync_1) = 'lg_t_sync_1'
138 0 : binary_history_column_name(bh_lg_t_sync_2) = 'lg_t_sync_2'
139 0 : binary_history_column_name(bh_star_1_mass) = 'star_1_mass'
140 0 : binary_history_column_name(bh_lg_star_1_mass) = 'lg_star_1_mass'
141 0 : binary_history_column_name(bh_star_2_mass) = 'star_2_mass'
142 0 : binary_history_column_name(bh_lg_star_2_mass) = 'lg_star_2_mass'
143 0 : binary_history_column_name(bh_sum_of_masses) = 'sum_of_masses'
144 0 : binary_history_column_name(bh_mass_ratio) = 'mass_ratio'
145 0 : binary_history_column_name(bh_obs_mass_ratio) = 'obs_mass_ratio'
146 0 : binary_history_column_name(bh_lg_mtransfer_rate) = 'lg_mtransfer_rate'
147 0 : binary_history_column_name(bh_lg_mstar_dot_1) = 'lg_mstar_dot_1'
148 0 : binary_history_column_name(bh_lg_mstar_dot_2) = 'lg_mstar_dot_2'
149 0 : binary_history_column_name(bh_lg_system_mdot_1) = 'lg_system_mdot_1'
150 0 : binary_history_column_name(bh_lg_system_mdot_2) = 'lg_system_mdot_2'
151 0 : binary_history_column_name(bh_lg_wind_mdot_1) = 'lg_wind_mdot_1'
152 0 : binary_history_column_name(bh_lg_wind_mdot_2) = 'lg_wind_mdot_2'
153 0 : binary_history_column_name(bh_star_1_div_star_2_mass) = 'star_1_div_star_2_mass'
154 0 : binary_history_column_name(bh_delta_star_1_mass) = 'delta_star_1_mass'
155 0 : binary_history_column_name(bh_delta_star_2_mass) = 'delta_star_2_mass'
156 0 : binary_history_column_name(bh_fixed_xfer_fraction) = 'fixed_xfer_fraction'
157 0 : binary_history_column_name(bh_eff_xfer_fraction) = 'eff_xfer_fraction'
158 0 : binary_history_column_name(bh_lg_mdot_edd) = 'lg_mdot_edd'
159 0 : binary_history_column_name(bh_mdot_edd_eta) = 'mdot_edd_eta'
160 0 : binary_history_column_name(bh_lg_accretion_luminosity) = 'lg_accretion_luminosity'
161 0 : binary_history_column_name(bh_bh_spin) = 'bh_spin'
162 0 : binary_history_column_name(bh_v_orb_1) = 'v_orb_1'
163 0 : binary_history_column_name(bh_v_orb_2) = 'v_orb_2'
164 0 : binary_history_column_name(bh_lg_F_irr) = 'lg_F_irr'
165 0 : binary_history_column_name(bh_J_orb) = 'J_orb'
166 0 : binary_history_column_name(bh_J_spin_1) = 'J_spin_1'
167 0 : binary_history_column_name(bh_J_spin_2) = 'J_spin_2'
168 0 : binary_history_column_name(bh_J_total) = 'J_total'
169 0 : binary_history_column_name(bh_Jdot) = 'Jdot'
170 0 : binary_history_column_name(bh_jdot_mb) = 'jdot_mb'
171 0 : binary_history_column_name(bh_jdot_gr) = 'jdot_gr'
172 0 : binary_history_column_name(bh_jdot_ml) = 'jdot_ml'
173 0 : binary_history_column_name(bh_jdot_ls) = 'jdot_ls'
174 0 : binary_history_column_name(bh_jdot_missing_wind) = 'jdot_missing_wind'
175 0 : binary_history_column_name(bh_extra_jdot) = 'extra_jdot'
176 0 : binary_history_column_name(bh_accretion_mode) = 'accretion_mode'
177 0 : binary_history_column_name(bh_acc_am_div_kep_am) = 'acc_am_div_kep_am'
178 0 : binary_history_column_name(bh_edot) = 'edot'
179 0 : binary_history_column_name(bh_edot_tidal) = 'edot_tidal'
180 0 : binary_history_column_name(bh_edot_enhance) = 'edot_enhance'
181 0 : binary_history_column_name(bh_extra_edot) = 'extra_edot'
182 0 : binary_history_column_name(bh_point_mass_index) = 'point_mass_index'
183 0 : binary_history_column_name(bh_ignore_rlof_flag) = 'ignore_rlof_flag'
184 0 : binary_history_column_name(bh_model_twins_flag) = 'model_twins_flag'
185 0 : binary_history_column_name(bh_CE_flag) = 'CE_flag'
186 0 : binary_history_column_name(bh_CE_lambda1) = 'CE_lambda1'
187 0 : binary_history_column_name(bh_CE_lambda2) = 'CE_lambda2'
188 0 : binary_history_column_name(bh_CE_Ebind1) = 'CE_Ebind1'
189 0 : binary_history_column_name(bh_CE_Ebind2) = 'CE_Ebind2'
190 0 : binary_history_column_name(bh_CE_num1) = 'CE_num1'
191 0 : binary_history_column_name(bh_CE_num2) = 'CE_num2'
192 :
193 0 : cnt = 0
194 0 : do i=1,bh_col_id_max
195 0 : if (len_trim(binary_history_column_name(i)) == 0) then
196 0 : write(*,*) 'missing name for log column id', i
197 0 : if (i > 1) write(*,*) 'following ' // trim(binary_history_column_name(i-1))
198 0 : write(*,*)
199 0 : cnt = cnt+1
200 : end if
201 : end do
202 :
203 0 : if (cnt > 0) then
204 0 : ierr = -1
205 0 : return
206 : end if
207 :
208 : end subroutine binary_history_column_names_init
209 :
210 0 : subroutine binary_private_def_init
211 : use num_def
212 : use utils_lib, only: get_compiler_version, get_mesasdk_version
213 :
214 : integer :: i
215 : logical :: okay
216 : integer :: ierr
217 :
218 : include 'formats'
219 :
220 0 : okay = .true.
221 0 : ierr = 0
222 :
223 0 : binary_dt_why_str(1:b_numTlim) = ''
224 :
225 0 : binary_dt_why_str(b_Tlim_comp) = 'b_companion'
226 0 : binary_dt_why_str(b_Tlim_roche) = 'b_RL'
227 0 : binary_dt_why_str(b_Tlim_jorb) = 'b_jorb'
228 0 : binary_dt_why_str(b_Tlim_env) = 'b_envelope'
229 0 : binary_dt_why_str(b_Tlim_sep) = 'b_separation'
230 0 : binary_dt_why_str(b_Tlim_ecc) = 'b_eccentricity'
231 0 : binary_dt_why_str(b_Tlim_dm) = 'b_deltam'
232 :
233 0 : do i=1,b_numTlim
234 0 : if (len_trim(binary_dt_why_str(i)) == 0) then
235 0 : if (i > 1) then
236 0 : write(*,2) 'missing binary_dt_why_str following ' // trim(binary_dt_why_str(i-1)), i
237 : else
238 0 : write(*,2) 'missing binary_dt_why_str 1'
239 : end if
240 : okay = .false.
241 : end if
242 : end do
243 :
244 0 : if (.not. okay) call mesa_error(__FILE__,__LINE__,'binary_private_def_init')
245 :
246 :
247 : !here we store useful information about the compiler and SDK
248 0 : call get_compiler_version(compiler_name,compiler_version_name)
249 0 : call get_mesasdk_version(mesasdk_version_name,ierr)
250 0 : call date_and_time(date=date)
251 :
252 0 : end subroutine binary_private_def_init
253 :
254 1 : integer function alloc_binary(ierr)
255 : integer, intent(out) :: ierr
256 : integer :: i
257 : type (binary_info), pointer :: b
258 :
259 1 : ierr = 0
260 1 : alloc_binary = -1
261 2 : !$omp critical (binary_handle)
262 1 : if (.not. have_initialized_binary_handles) then
263 11 : do i = 1, max_binary_handles
264 10 : binary_handles(i)% binary_id = i
265 11 : binary_handles(i)% in_use = .false.
266 : end do
267 1 : have_initialized_binary_handles = .true.
268 : end if
269 1 : do i = 1, max_binary_handles
270 1 : if (.not. binary_handles(i)% in_use) then
271 1 : binary_handles(i)% in_use = .true.
272 1 : alloc_binary = i
273 1 : exit
274 : end if
275 : end do
276 : !$omp end critical (binary_handle)
277 1 : if (alloc_binary == -1) then
278 0 : ierr = -1
279 0 : return
280 : end if
281 1 : if (binary_handles(alloc_binary)% binary_id /= alloc_binary) then
282 0 : ierr = -1
283 0 : return
284 : end if
285 1 : b => binary_handles(alloc_binary)
286 :
287 : end function alloc_binary
288 :
289 :
290 0 : subroutine free_binary(b)
291 : type (binary_info), pointer :: b
292 0 : binary_handles(b% binary_id)% in_use = .false.
293 0 : end subroutine free_binary
294 :
295 :
296 : end module binary_private_def
297 :
|