Line data Source code
1 : ! ***********************************************************************
2 : !
3 : ! Copyright (C) 2022 The MESA Team & Matthias Fabry
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 pgbinary_star
21 :
22 : use const_def, only: dp, msun
23 : use binary_def
24 : use pgbinary_support
25 :
26 : implicit none
27 :
28 : contains
29 :
30 :
31 0 : subroutine Star1_plot(id, device_id, ierr)
32 : integer, intent(in) :: id, device_id
33 : integer, intent(out) :: ierr
34 : type (binary_info), pointer :: b
35 : ierr = 0
36 0 : call get_binary_ptr(id, b, ierr)
37 0 : if (ierr /= 0) return
38 0 : call pgslct(device_id)
39 0 : call pgbbuf()
40 0 : call pgeras()
41 : call do_Star1_plot(b, id, device_id, &
42 : b% pg% Star1_xleft, b% pg% Star1_xright, &
43 : b% pg% Star1_ybot, b% pg% Star1_ytop, .false., b% pg% Star1_title, &
44 0 : b% pg% Star1_txt_scale_factor, b% pg% Star1_plot_name, ierr)
45 0 : call pgebuf()
46 : end subroutine Star1_plot
47 :
48 0 : subroutine do_Star1_plot(b, id, device_id, &
49 : vp_xleft, vp_xright, vp_ybot, vp_ytop, &
50 : subplot, title, txt_scale, plot_name, ierr)
51 : type (binary_info), pointer :: b
52 : integer, intent(in) :: id, device_id
53 : real, intent(in) :: vp_xleft, vp_xright, vp_ybot, vp_ytop, txt_scale
54 : logical, intent(in) :: subplot
55 : character (len = *), intent(in) :: title, plot_name
56 : integer, intent(out) :: ierr
57 : call do_star_plot(b, id, device_id, &
58 : vp_xleft, vp_xright, vp_ybot, vp_ytop, subplot, title, txt_scale, &
59 0 : plot_name, 1, ierr)
60 0 : end subroutine do_Star1_plot
61 :
62 0 : subroutine Star2_plot(id, device_id, ierr)
63 : integer, intent(in) :: id, device_id
64 : integer, intent(out) :: ierr
65 : type (binary_info), pointer :: b
66 : ierr = 0
67 0 : call get_binary_ptr(id, b, ierr)
68 0 : if (ierr /= 0) return
69 0 : call pgslct(device_id)
70 0 : call pgbbuf()
71 0 : call pgeras()
72 : call do_Star2_plot(b, id, device_id, &
73 : b% pg% Star2_xleft, b% pg% Star2_xright, &
74 : b% pg% Star2_ybot, b% pg% Star2_ytop, .false., b% pg% Star2_title, &
75 0 : b% pg% Star2_txt_scale_factor, b% pg% Star2_plot_name, ierr)
76 0 : call pgebuf()
77 : end subroutine Star2_plot
78 :
79 0 : subroutine do_Star2_plot(b, id, device_id, &
80 : vp_xleft, vp_xright, vp_ybot, vp_ytop, &
81 : subplot, title, txt_scale, plot_name, ierr)
82 : type (binary_info), pointer :: b
83 : integer, intent(in) :: id, device_id
84 : real, intent(in) :: vp_xleft, vp_xright, vp_ybot, vp_ytop, txt_scale
85 : logical, intent(in) :: subplot
86 : character (len = *), intent(in) :: title, plot_name
87 : integer, intent(out) :: ierr
88 : call do_star_plot(b, id, device_id, &
89 : vp_xleft, vp_xright, vp_ybot, vp_ytop, subplot, title, txt_scale, &
90 0 : plot_name, 2, ierr)
91 0 : end subroutine do_Star2_plot
92 :
93 0 : subroutine do_star_plot(b, id, device_id, xleft, xright, &
94 : ybot, ytop, subplot, Star_title, Star_txt_scale_factor, &
95 : Star_plot_name, Star_number, ierr)
96 :
97 : use utils_lib, only : StrLowCase
98 : use star_lib, only : read_pgstar_inlist
99 : use pgstar, only : update_pgstar_data, update_pgstar_history_file
100 : use pgstar_grid, only : do_grid1_plot, do_grid2_plot, do_grid3_plot, &
101 : do_grid4_plot, do_grid5_plot, do_grid6_plot, do_grid7_plot, &
102 : do_grid8_plot, do_grid9_plot
103 : use pgstar_kipp, only : do_Kipp_Plot
104 : use pgstar_L_R, only : do_L_R_Plot
105 : use pgstar_L_v, only : do_L_v_Plot
106 : use pgstar_L_Teff, only : do_L_Teff_Plot
107 : use pgstar_logL_R, only : do_logL_R_Plot
108 : use pgstar_logL_v, only : do_logL_v_Plot
109 : use pgstar_logL_Teff, only : do_logL_Teff_Plot
110 : use pgstar_r_L, only : do_R_L_Plot
111 : use pgstar_r_Teff, only : do_R_Teff_Plot
112 : use pgstar_logg_Teff, only : do_logg_Teff_Plot
113 : use pgstar_logg_logT, only : do_logg_logT_Plot
114 : use pgstar_dPg_dnu, only : do_dPg_dnu_Plot
115 : use pgstar_hr, only : do_HR_Plot
116 : use pgstar_trho, only : do_TRho_Plot
117 : use pgstar_dynamo, only : do_Dynamo_plot
118 : use pgstar_mixing_Ds, only : do_Mixing_plot
119 : use pgstar_trho_profile, only : do_TRho_Profile_plot
120 : use pgstar_power, only : do_power_plot
121 : use pgstar_mode_prop, only : do_mode_propagation_plot
122 : use pgstar_abundance, only : do_abundance_plot
123 : use pgstar_summary_burn, only : do_summary_burn_plot
124 : use pgstar_summary_profile, only : do_summary_profile_plot
125 : use pgstar_summary_history, only : do_summary_history_plot
126 : use pgstar_network, only : do_network_plot
127 : use pgstar_production, only : do_production_plot
128 : use pgstar_summary, only : &
129 : do_Text_Summary1_plot, do_Text_Summary2_plot, do_Text_Summary3_plot, &
130 : do_Text_Summary4_plot, do_Text_Summary5_plot, do_Text_Summary6_plot, &
131 : do_Text_Summary7_plot, do_Text_Summary8_plot, do_Text_Summary9_plot
132 : use pgstar_profile_panels, only : &
133 : do_Profile_Panels1_plot, do_Profile_Panels2_plot, do_Profile_Panels3_plot, &
134 : do_Profile_Panels4_plot, do_Profile_Panels5_plot, do_Profile_Panels6_plot, &
135 : do_Profile_Panels7_plot, do_Profile_Panels8_plot, do_Profile_Panels9_plot
136 : use pgstar_history_panels, only : &
137 : do_History_Panels1_plot, do_History_Panels2_plot, do_History_Panels3_plot, &
138 : do_History_Panels4_plot, do_History_Panels5_plot, do_History_Panels6_plot, &
139 : do_History_Panels7_plot, do_History_Panels8_plot, do_History_Panels9_plot
140 : use pgstar_hist_track, only : &
141 : do_History_Track1_plot, do_History_Track2_plot, do_History_Track3_plot, &
142 : do_History_Track4_plot, do_History_Track5_plot, do_History_Track6_plot, &
143 : do_History_Track7_plot, do_History_Track8_plot, do_History_Track9_plot
144 : use pgstar_Color_Magnitude, only : &
145 : do_Color_Magnitude1_plot, do_Color_Magnitude2_plot, do_Color_Magnitude3_plot, &
146 : do_Color_Magnitude4_plot, do_Color_Magnitude5_plot, do_Color_Magnitude6_plot, &
147 : do_Color_Magnitude7_plot, do_Color_Magnitude8_plot, do_Color_Magnitude9_plot
148 :
149 : type (binary_info), pointer :: b
150 : logical, intent(in) :: subplot
151 : integer, intent(in) :: id, device_id, star_number
152 : real, intent(in) :: xleft, xright, ybot, ytop, Star_txt_scale_factor
153 : character (len = *), intent(in) :: Star_title, Star_plot_name
154 : integer, intent(out) :: ierr
155 :
156 : character (len = strlen) :: title, status, mass
157 : logical, parameter :: star_subplot = .true.
158 :
159 : include 'formats'
160 :
161 0 : call pgsave
162 0 : call pgsvp(xleft, xright, ybot, ytop) ! set viewport
163 0 : if (.not. subplot) then ! do title stuff
164 0 : call show_model_number_pgbinary(b)
165 0 : call show_age_pgbinary(b)
166 : end if
167 0 : if (b% pg% show_mtrans_status) then
168 0 : if (Star_title /= '') title = trim(Star_title) // ":"
169 0 : status = ' Detached'
170 0 : if (b% mtransfer_rate /= 0d0) then
171 0 : if (b% d_i == star_number) then
172 0 : status = ' Donor'
173 : else
174 0 : status = ' Accretor'
175 : end if
176 : end if
177 0 : title = trim(title) // status
178 : end if
179 0 : call show_grid_title_pgbinary(b, title)
180 0 : call pgunsa
181 :
182 0 : ierr = 0
183 :
184 0 : select case(star_number)
185 : case(1)
186 0 : if (b% pg% do_star1_box) then
187 : call pgsvp(xleft + b% pg% Star1_box_pad_left, &
188 : xright + b% pg% Star1_box_pad_right, &
189 0 : ybot + b% pg% Star1_box_pad_bot, ytop + b% pg% Star1_box_pad_top)
190 0 : call draw_rect()
191 0 : call pgsvp(xleft, xright, ybot, ytop)
192 : end if
193 0 : if (b% point_mass_i /= 1) then
194 0 : call read_pgstar_inlist(b% s1, b% job% inlist_names(1), ierr)
195 0 : call update_pgstar_data(b% s1, ierr)
196 0 : call plot_case(b% s1, b% star_ids(1))
197 0 : call update_pgstar_history_file(b% s1, ierr)
198 : else
199 0 : write(mass, '(f0.2)') b% m(1) / Msun
200 0 : call pgmtxt('T', -2.0, 0.5, 0.5, 'Star 1 not simulated')
201 0 : call pgmtxt('T', -3.0, 0.5, 0.5, 'point mass of ' // trim(adjustl(mass)) // ' M\d\(2281)')
202 : end if
203 : case(2)
204 0 : if (b% pg% do_star2_box) then
205 : call pgsvp(xleft + b% pg% Star2_box_pad_left, &
206 : xright + b% pg% Star2_box_pad_right, &
207 0 : ybot + b% pg% Star2_box_pad_bot, ytop + b% pg% Star2_box_pad_top)
208 0 : call draw_rect()
209 0 : call pgsvp(xleft, xright, ybot, ytop)
210 : end if
211 0 : if (b% point_mass_i /= 2) then
212 0 : call read_pgstar_inlist(b% s2, b% job% inlist_names(2), ierr)
213 0 : call update_pgstar_data(b% s2, ierr)
214 0 : call plot_case(b% s2, b% star_ids(2))
215 0 : call update_pgstar_history_file(b% s2, ierr)
216 : else
217 0 : write(mass, '(f0.2)') b% m(2) / Msun
218 0 : call pgmtxt('T', -2.0, 0.5, 0.5, 'Star 2 not simulated')
219 0 : call pgmtxt('T', -3.0, 0.5, 0.5, 'point mass of ' // trim(adjustl(mass)) // ' M\d\(2281)')
220 : end if
221 : end select
222 :
223 : contains
224 :
225 0 : subroutine plot_case(s, star_id)
226 : type (star_info), pointer, intent(in) :: s
227 : integer, intent(in) :: star_id
228 : type (pgstar_win_file_data), pointer :: p
229 : integer :: plot_id, j
230 : logical :: found_it
231 :
232 0 : select case(StrLowCase(Star_plot_name))
233 : case ('abundance')
234 : call do_abundance_plot(&
235 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, &
236 0 : s% pg% Abundance_title, Star_txt_scale_factor * s% pg% Abundance_txt_scale, ierr)
237 : case ('power')
238 : call do_power_plot(&
239 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, &
240 0 : s% pg% Power_title, Star_txt_scale_factor * s% pg% Power_txt_scale, ierr)
241 : case ('mixing')
242 : call do_Mixing_plot(&
243 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, &
244 0 : s% pg% Mixing_title, Star_txt_scale_factor * s% pg% Mixing_txt_scale, ierr)
245 : case ('dynamo')
246 : call do_Dynamo_plot(&
247 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, &
248 0 : s% pg% Dynamo_title, Star_txt_scale_factor * s% pg% Dynamo_txt_scale, ierr)
249 : case ('trho')
250 : call do_TRho_plot(&
251 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, &
252 0 : s% pg% TRho_title, Star_txt_scale_factor * s% pg% TRho_txt_scale, ierr)
253 : case ('mode_prop')
254 : call do_mode_propagation_plot(&
255 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Mode_Prop_title, &
256 0 : Star_txt_scale_factor * s% pg% Mode_Prop_txt_scale, ierr)
257 : case ('summary_burn')
258 : call do_summary_burn_plot(&
259 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Summary_Burn_title, &
260 0 : Star_txt_scale_factor * s% pg% Summary_Burn_txt_scale, ierr)
261 : case ('summary_profile')
262 : call do_summary_profile_plot(&
263 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Summary_Profile_title, &
264 0 : Star_txt_scale_factor * s% pg% Summary_Profile_txt_scale, ierr)
265 : case ('summary_history')
266 : call do_summary_history_plot(&
267 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Summary_History_title, &
268 0 : Star_txt_scale_factor * s% pg% Summary_History_txt_scale, ierr)
269 : case ('trho_profile')
270 : call do_TRho_Profile_plot(&
271 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% TRho_Profile_title, &
272 0 : Star_txt_scale_factor * s% pg% TRho_Profile_txt_scale, ierr)
273 : case ('profile_panels1')
274 : call do_Profile_Panels1_plot(&
275 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Profile_Panels1_title, &
276 0 : Star_txt_scale_factor * s% pg% Profile_Panels1_txt_scale, ierr)
277 : case ('profile_panels2')
278 : call do_Profile_Panels2_plot(&
279 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Profile_Panels2_title, &
280 0 : Star_txt_scale_factor * s% pg% Profile_Panels2_txt_scale, ierr)
281 : case ('profile_panels3')
282 : call do_Profile_Panels3_plot(&
283 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Profile_Panels3_title, &
284 0 : Star_txt_scale_factor * s% pg% Profile_Panels3_txt_scale, ierr)
285 : case ('profile_panels4')
286 : call do_Profile_Panels4_plot(&
287 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Profile_Panels4_title, &
288 0 : Star_txt_scale_factor * s% pg% Profile_Panels4_txt_scale, ierr)
289 : case ('profile_panels5')
290 : call do_Profile_Panels5_plot(&
291 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Profile_Panels5_title, &
292 0 : Star_txt_scale_factor * s% pg% Profile_Panels5_txt_scale, ierr)
293 : case ('profile_panels6')
294 : call do_Profile_Panels6_plot(&
295 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Profile_Panels6_title, &
296 0 : Star_txt_scale_factor * s% pg% Profile_Panels6_txt_scale, ierr)
297 : case ('profile_panels7')
298 : call do_Profile_Panels7_plot(&
299 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Profile_Panels7_title, &
300 0 : Star_txt_scale_factor * s% pg% Profile_Panels7_txt_scale, ierr)
301 : case ('profile_panels8')
302 : call do_Profile_Panels8_plot(&
303 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Profile_Panels8_title, &
304 0 : Star_txt_scale_factor * s% pg% Profile_Panels8_txt_scale, ierr)
305 : case ('profile_panels9')
306 : call do_Profile_Panels9_plot(&
307 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Profile_Panels9_title, &
308 0 : Star_txt_scale_factor * s% pg% Profile_Panels9_txt_scale, ierr)
309 : case ('logg_teff')
310 : call do_logg_Teff_plot(&
311 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% logg_Teff_title, &
312 0 : Star_txt_scale_factor * s% pg% logg_Teff_txt_scale, ierr)
313 : case ('logg_logt')
314 : call do_logg_logT_plot(&
315 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% logg_logT_title, &
316 0 : Star_txt_scale_factor * s% pg% logg_logT_txt_scale, ierr)
317 : case ('hr')
318 : call do_HR_plot(&
319 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% HR_title, &
320 0 : Star_txt_scale_factor * s% pg% HR_txt_scale, ierr)
321 : case ('logl_r')
322 : call do_logL_R_plot(&
323 : s, star_id, device_id, s% pg% show_logL_photosphere_r, xleft, xright, ybot, ytop, &
324 : star_subplot, s% pg% logL_R_title, &
325 0 : Star_txt_scale_factor * s% pg% logL_R_txt_scale, ierr)
326 : case ('logl_v')
327 : call do_logL_v_plot(&
328 : s, star_id, device_id, s% pg% show_logL_photosphere_v, xleft, xright, ybot, ytop, &
329 : star_subplot, s% pg% logL_v_title, &
330 0 : Star_txt_scale_factor * s% pg% logL_v_txt_scale, ierr)
331 : case ('logl_teff')
332 : call do_logL_Teff_plot(&
333 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% logL_Teff_title, &
334 0 : Star_txt_scale_factor * s% pg% logL_Teff_txt_scale, ierr)
335 : case ('l_r')
336 : call do_L_R_plot(&
337 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% L_R_title, &
338 0 : Star_txt_scale_factor * s% pg% L_R_txt_scale, ierr)
339 : case ('l_v')
340 : call do_L_v_plot(&
341 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% L_v_title, &
342 0 : Star_txt_scale_factor * s% pg% L_v_txt_scale, ierr)
343 : case ('l_teff')
344 : call do_L_Teff_plot(&
345 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% L_Teff_title, &
346 0 : Star_txt_scale_factor * s% pg% L_Teff_txt_scale, ierr)
347 : case ('r_l')
348 : call do_R_L_plot(&
349 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% R_L_title, &
350 0 : Star_txt_scale_factor * s% pg% R_L_txt_scale, ierr)
351 : case ('r_teff')
352 : call do_R_Teff_plot(&
353 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% R_Teff_title, &
354 0 : Star_txt_scale_factor * s% pg% R_Teff_txt_scale, ierr)
355 : case ('dpg_dnu')
356 : call do_dPg_dnu_plot(&
357 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% dPg_dnu_title, &
358 0 : Star_txt_scale_factor * s% pg% dPg_dnu_txt_scale, ierr)
359 : case ('history_panels1')
360 : call do_History_Panels1_plot(&
361 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% History_Panels1_title, &
362 0 : Star_txt_scale_factor * s% pg% History_Panels1_txt_scale, ierr)
363 : case ('history_panels2')
364 : call do_History_Panels2_plot(&
365 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% History_Panels2_title, &
366 0 : Star_txt_scale_factor * s% pg% History_Panels2_txt_scale, ierr)
367 : case ('history_panels3')
368 : call do_History_Panels3_plot(&
369 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% History_Panels3_title, &
370 0 : Star_txt_scale_factor * s% pg% History_Panels3_txt_scale, ierr)
371 : case ('history_panels4')
372 : call do_History_Panels4_plot(&
373 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% History_Panels4_title, &
374 0 : Star_txt_scale_factor * s% pg% History_Panels4_txt_scale, ierr)
375 : case ('history_panels5')
376 : call do_History_Panels5_plot(&
377 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% History_Panels5_title, &
378 0 : Star_txt_scale_factor * s% pg% History_Panels5_txt_scale, ierr)
379 : case ('history_panels6')
380 : call do_History_Panels6_plot(&
381 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% History_Panels6_title, &
382 0 : Star_txt_scale_factor * s% pg% History_Panels6_txt_scale, ierr)
383 : case ('history_panels7')
384 : call do_History_Panels7_plot(&
385 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% History_Panels7_title, &
386 0 : Star_txt_scale_factor * s% pg% History_Panels7_txt_scale, ierr)
387 : case ('history_panels8')
388 : call do_History_Panels8_plot(&
389 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% History_Panels8_title, &
390 0 : Star_txt_scale_factor * s% pg% History_Panels8_txt_scale, ierr)
391 : case ('history_panels9')
392 : call do_History_Panels9_plot(&
393 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% History_Panels9_title, &
394 0 : Star_txt_scale_factor * s% pg% History_Panels9_txt_scale, ierr)
395 : case ('color_magnitude1')
396 : call do_Color_Magnitude1_plot(&
397 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Color_Magnitude1_title, &
398 0 : Star_txt_scale_factor * s% pg% Color_Magnitude1_txt_scale, ierr)
399 : case ('color_magnitude2')
400 : call do_Color_Magnitude2_plot(&
401 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Color_Magnitude2_title, &
402 0 : Star_txt_scale_factor * s% pg% Color_Magnitude2_txt_scale, ierr)
403 : case ('color_magnitude3')
404 : call do_Color_Magnitude3_plot(&
405 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Color_Magnitude3_title, &
406 0 : Star_txt_scale_factor * s% pg% Color_Magnitude3_txt_scale, ierr)
407 : case ('color_magnitude4')
408 : call do_Color_Magnitude4_plot(&
409 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Color_Magnitude4_title, &
410 0 : Star_txt_scale_factor * s% pg% Color_Magnitude4_txt_scale, ierr)
411 : case ('color_magnitude5')
412 : call do_Color_Magnitude5_plot(&
413 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Color_Magnitude5_title, &
414 0 : Star_txt_scale_factor * s% pg% Color_Magnitude5_txt_scale, ierr)
415 : case ('color_magnitude6')
416 : call do_Color_Magnitude6_plot(&
417 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Color_Magnitude6_title, &
418 0 : Star_txt_scale_factor * s% pg% Color_Magnitude6_txt_scale, ierr)
419 : case ('color_magnitude7')
420 : call do_Color_Magnitude7_plot(&
421 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Color_Magnitude7_title, &
422 0 : Star_txt_scale_factor * s% pg% Color_Magnitude7_txt_scale, ierr)
423 : case ('color_magnitude8')
424 : call do_Color_Magnitude8_plot(&
425 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Color_Magnitude8_title, &
426 0 : Star_txt_scale_factor * s% pg% Color_Magnitude8_txt_scale, ierr)
427 : case ('color_magnitude9')
428 : call do_Color_Magnitude9_plot(&
429 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Color_Magnitude9_title, &
430 0 : Star_txt_scale_factor * s% pg% Color_Magnitude9_txt_scale, ierr)
431 : case ('history_track1')
432 : call do_History_Track1_plot(&
433 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% History_Track1_title, &
434 0 : Star_txt_scale_factor * s% pg% History_Track1_txt_scale, ierr)
435 : case ('history_track2')
436 : call do_History_Track2_plot(&
437 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% History_Track2_title, &
438 0 : Star_txt_scale_factor * s% pg% History_Track2_txt_scale, ierr)
439 : case ('history_track3')
440 : call do_History_Track3_plot(&
441 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% History_Track3_title, &
442 0 : Star_txt_scale_factor * s% pg% History_Track3_txt_scale, ierr)
443 : case ('history_track4')
444 : call do_History_Track4_plot(&
445 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% History_Track4_title, &
446 0 : Star_txt_scale_factor * s% pg% History_Track4_txt_scale, ierr)
447 : case ('history_track5')
448 : call do_History_Track5_plot(&
449 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% History_Track5_title, &
450 0 : Star_txt_scale_factor * s% pg% History_Track5_txt_scale, ierr)
451 : case ('history_track6')
452 : call do_History_Track6_plot(&
453 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% History_Track6_title, &
454 0 : Star_txt_scale_factor * s% pg% History_Track6_txt_scale, ierr)
455 : case ('history_track7')
456 : call do_History_Track7_plot(&
457 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% History_Track7_title, &
458 0 : Star_txt_scale_factor * s% pg% History_Track7_txt_scale, ierr)
459 : case ('history_track8')
460 : call do_History_Track8_plot(&
461 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% History_Track8_title, &
462 0 : Star_txt_scale_factor * s% pg% History_Track8_txt_scale, ierr)
463 : case ('history_track9')
464 : call do_History_Track9_plot(&
465 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% History_Track9_title, &
466 0 : Star_txt_scale_factor * s% pg% History_Track9_txt_scale, ierr)
467 : case ('kipp')
468 : call do_Kipp_plot(&
469 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Kipp_title, &
470 0 : Star_txt_scale_factor * s% pg% Kipp_txt_scale, ierr)
471 : case ('network')
472 : call do_Network_plot(&
473 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Network_title, &
474 0 : Star_txt_scale_factor * s% pg% Network_txt_scale, ierr)
475 : case ('production')
476 : call do_Production_plot(&
477 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Production_title, &
478 0 : Star_txt_scale_factor * s% pg% Production_txt_scale, ierr)
479 : case ('text_summary1')
480 : call do_Text_Summary1_plot(&
481 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Text_Summary1_title, &
482 0 : Star_txt_scale_factor * s% pg% Text_Summary1_txt_scale, s% pg% Text_Summary1_dxval, ierr)
483 : case ('text_summary2')
484 : call do_Text_Summary2_plot(&
485 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Text_Summary2_title, &
486 0 : Star_txt_scale_factor * s% pg% Text_Summary2_txt_scale, s% pg% Text_Summary2_dxval, ierr)
487 : case ('text_summary3')
488 : call do_Text_Summary3_plot(&
489 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Text_Summary3_title, &
490 0 : Star_txt_scale_factor * s% pg% Text_Summary3_txt_scale, s% pg% Text_Summary3_dxval, ierr)
491 : case ('text_summary4')
492 : call do_Text_Summary4_plot(&
493 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Text_Summary4_title, &
494 0 : Star_txt_scale_factor * s% pg% Text_Summary4_txt_scale, s% pg% Text_Summary4_dxval, ierr)
495 : case ('text_summary5')
496 : call do_Text_Summary5_plot(&
497 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Text_Summary5_title, &
498 0 : Star_txt_scale_factor * s% pg% Text_Summary5_txt_scale, s% pg% Text_Summary5_dxval, ierr)
499 : case ('text_summary6')
500 : call do_Text_Summary6_plot(&
501 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Text_Summary6_title, &
502 0 : Star_txt_scale_factor * s% pg% Text_Summary6_txt_scale, s% pg% Text_Summary6_dxval, ierr)
503 : case ('text_summary7')
504 : call do_Text_Summary7_plot(&
505 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Text_Summary7_title, &
506 0 : Star_txt_scale_factor * s% pg% Text_Summary7_txt_scale, s% pg% Text_Summary7_dxval, ierr)
507 : case ('text_summary8')
508 : call do_Text_Summary8_plot(&
509 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Text_Summary8_title, &
510 0 : Star_txt_scale_factor * s% pg% Text_Summary8_txt_scale, s% pg% Text_Summary8_dxval, ierr)
511 : case ('text_summary9')
512 : call do_Text_Summary9_plot(&
513 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Text_Summary9_title, &
514 0 : Star_txt_scale_factor * s% pg% Text_Summary9_txt_scale, s% pg% Text_Summary9_dxval, ierr)
515 : case('grid1')
516 : call do_grid1_plot(&
517 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Grid1_title, &
518 0 : Star_txt_scale_factor * s% pg% Grid1_txt_scale_factor, ierr)
519 : case('grid2')
520 : call do_grid2_plot(&
521 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Grid2_title, &
522 0 : Star_txt_scale_factor * s% pg% Grid2_txt_scale_factor, ierr)
523 : case('grid3')
524 : call do_grid3_plot(&
525 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Grid3_title, &
526 0 : Star_txt_scale_factor * s% pg% Grid3_txt_scale_factor, ierr)
527 : case('grid4')
528 : call do_grid4_plot(&
529 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Grid4_title, &
530 0 : Star_txt_scale_factor * s% pg% Grid4_txt_scale_factor, ierr)
531 : case('grid5')
532 : call do_grid5_plot(&
533 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Grid5_title, &
534 0 : Star_txt_scale_factor * s% pg% Grid5_txt_scale_factor, ierr)
535 : case('grid6')
536 : call do_grid6_plot(&
537 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Grid6_title, &
538 0 : Star_txt_scale_factor * s% pg% Grid6_txt_scale_factor, ierr)
539 : case('grid7')
540 : call do_grid7_plot(&
541 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Grid7_title, &
542 0 : Star_txt_scale_factor * s% pg% Grid7_txt_scale_factor, ierr)
543 : case('grid8')
544 : call do_grid8_plot(&
545 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Grid8_title, &
546 0 : Star_txt_scale_factor * s% pg% Grid8_txt_scale_factor, ierr)
547 : case('grid9')
548 : call do_grid9_plot(&
549 : s, star_id, device_id, xleft, xright, ybot, ytop, star_subplot, s% pg% Grid9_title, &
550 0 : Star_txt_scale_factor * s% pg% Grid9_txt_scale_factor, ierr)
551 : case default
552 : ! check for "other" plot
553 0 : found_it = .false.
554 0 : do j = 1, max_num_Other_plots
555 0 : plot_id = i_Other + j - 1
556 0 : p => s% pg% pgstar_win_file_ptr(plot_id)
557 0 : if (p% okay_to_call_do_plot_in_grid .and. &
558 0 : StrLowCase(p% name) == StrLowCase(Star_plot_name)) then
559 : call p% do_plot_in_grid(&
560 : star_id, device_id, xleft, xright, ybot, ytop, &
561 0 : Star_txt_scale_factor, ierr)
562 0 : found_it = .true.
563 0 : exit
564 : end if
565 : end do
566 :
567 0 : if (.not. found_it) then
568 :
569 : write(*, *) 'FAILED TO RECOGNIZE NAME FOR STAR PLOT: ' &
570 0 : // trim(Star_plot_name)
571 : write(*, '(a)') &
572 0 : 'here are the valid names', &
573 0 : 'Kipp', &
574 0 : 'HR', &
575 0 : 'TRho', &
576 0 : 'R_Teff', &
577 0 : 'R_L', &
578 0 : 'L_Teff', &
579 0 : 'L_R', &
580 0 : 'L_v', &
581 0 : 'logL_Teff', &
582 0 : 'logL_R', &
583 0 : 'logL_v', &
584 0 : 'logg_Teff', &
585 0 : 'logg_logT', &
586 0 : 'dPg_dnu', &
587 0 : 'TRho_Profile', &
588 0 : 'Summary_Burn', &
589 0 : 'Summary_Profile', &
590 0 : 'Summary_History', &
591 0 : 'Abundance', &
592 0 : 'Network', &
593 0 : 'Production', &
594 0 : 'Power', &
595 0 : 'Dynamo', &
596 0 : 'Mixing', &
597 0 : 'Mode_Prop', &
598 0 : 'Text_Summary1,..,9', &
599 0 : 'Profile_Panels1,..,9', &
600 0 : 'History_Panels1,..,9', &
601 0 : 'History_Tracks1,..,9', &
602 0 : 'Color_Magnitude1,..,9', &
603 0 : 'Grid1,..,9', &
604 0 : 'and if you are using star/astero', &
605 0 : 'Echelle', &
606 0 : 'Ratios'
607 0 : write(*, *)
608 :
609 : end if
610 :
611 : end select
612 :
613 0 : end subroutine plot_case
614 :
615 : end subroutine do_star_plot
616 :
617 :
618 : end module pgbinary_star
|