Blame view

LabTools/IRAP/JPB/make_phangs_ssps_isrf_prediction.pro 6.99 KB
ccbd30b1   Jean-Philippe Bernard   First commit
1
2
PRO make_phangs_ssps_isrf_prediction,source_name=source_name,save=save,help=help

ccbd30b1   Jean-Philippe Bernard   First commit
3
4
5
6
;+
; NAME:
;       make_phangs_ssps_isrf_prediction
; CALLING SEQUENCE:
14ae4f23   Jean-Philippe Bernard   improved
7
;       make_phangs_ssps_isrf_prediction[,source_name=][,/save][,/help]
ccbd30b1   Jean-Philippe Bernard   First commit
8
; PURPOSE:
eb7ea183   Jean-Philippe Bernard   included stellar ...
9
10
;       predicts the minimum ISRF in voronoi bins. The prediction is scaled to the Muse filter data observations.
;       It is computed from the un-redenned stellar emission using dustem_plugin_phangs_stellar_continuum.pro
ccbd30b1   Jean-Philippe Bernard   First commit
11
12
13
14
15
16
17
18
19
20
21
22
; INPUTS:
;       None
; OPTIONAL KEYWORDS:
;       save        = if set, save the classes
;       help        = if set, print this help
; OUTPUTS:
;	    None
; OPTIONAL INPUT:
;       source_name = source name (default='ngc0628')
; OPTIONAL OUTPUT:
;       None
; PROCEDURE AND SUBROUTINE USED
eb7ea183   Jean-Philippe Bernard   included stellar ...
23
;       ISRF saved is the one predicted by dustem_plugin_phangs_stellar_isrf with no reddening, for each Muse Voronoi bin,
14ae4f23   Jean-Philippe Bernard   improved
24
25
;       scaled in amplitude to match the Muse filter data for that Voronoi bin.
;       The G0 value computed is wrt the Mathis field at 1 mic.
ccbd30b1   Jean-Philippe Bernard   First commit
26
; SIDE EFFECTS:
14ae4f23   Jean-Philippe Bernard   improved
27
;       produces file _isrf_min_prediction.sav
ccbd30b1   Jean-Philippe Bernard   First commit
28
; EXAMPLE:
14ae4f23   Jean-Philippe Bernard   improved
29
;       make_phangs_ssps_isrf_prediction,source_name='ngc0628',/save
ccbd30b1   Jean-Philippe Bernard   First commit
30
31
32
33
34
35
36
37
38
; MODIFICATION HISTORY:
;       written by Jean-Philippe Bernard
;-

IF keyword_set(help) THEN BEGIN
  doc_library,'make_phangs_ssps_isrf_prediction'
  goto,the_end
ENDIF

ccbd30b1   Jean-Philippe Bernard   First commit
39
40
41
42
win=0L
;window,win,xsize=900,ysize=1000 & win=win+1

;=== This is where the data is read from and the ISRFs will be stored
ccbd30b1   Jean-Philippe Bernard   First commit
43
44
45
46
47
48
49
50
data_dir=!phangs_data_dir+'/ISRF/WORK/'

use_model='DBP90'    ;Example with default keywords uses the DBP90 model
use_polarization=0   ; initialize Dustemwrap in no polarization mode 

;== INITIALISE DUSTEM
dustem_init,model=use_model,polarization=use_polarization,show_plots=show_plots

ccbd30b1   Jean-Philippe Bernard   First commit
51
52
53
use_source_name='ngc0628'
IF keyword_set(source_name) THEN use_source_name=source_name

997cc66d   Jean-Philippe Bernard   improved
54
object_distance=(phangs_get_galaxy_distance(use_source_name)).dist
ccbd30b1   Jean-Philippe Bernard   First commit
55
56
CASE use_source_name OF
	'ngc0628':BEGIN
997cc66d   Jean-Philippe Bernard   improved
57
		;object_distance=9.84  ;MPc
ccbd30b1   Jean-Philippe Bernard   First commit
58
59
		object_thickness=0.1  ;kpc
	END
82beee16   Jean-Philippe Bernard   improved
60
	'ngc3351':BEGIN
997cc66d   Jean-Philippe Bernard   improved
61
		;object_distance=9.96  ;MPc
82beee16   Jean-Philippe Bernard   improved
62
63
		object_thickness=0.1  ;kpc
	END
ccbd30b1   Jean-Philippe Bernard   First commit
64
65
ENDCASE

9b0b6d7e   Jean-Philippe Bernard   finished implemen...
66
reso_str=''
9b0b6d7e   Jean-Philippe Bernard   finished implemen...
67

ccbd30b1   Jean-Philippe Bernard   First commit
68
69
70
dustem_define_la_common
obp=[1.1,0,1.15,1]

4233645a   Jean-Philippe Bernard   improved
71
72
73
74
75
76
77
file=data_dir+use_source_name+'_muse_data'+reso_str+'.sav'
st_info=file_info(file)
IF st_info.exists NE 1 THEN BEGIN
	message,'Could not find '+file,/continue
	stop
ENDIF
restore,file,/verb
14ae4f23   Jean-Philippe Bernard   improved
78
79
80
81
82
83
84
;% RESTORE: Restored variable: ST_TEMPLATES.
;% RESTORE: Restored variable: ST_MUSE_WEIGHTS.
;% RESTORE: Restored variable: VORONOI_ID.
;% RESTORE: Restored variable: AGE_VALUES.
;% RESTORE: Restored variable: METALICITY_VALUES.
;% RESTORE: Restored variable: BINS.
;% RESTORE: Restored variable: HREF.
9b37a060   Jean-Philippe Bernard   improved for smoo...
85
;=== needed for muse_filters only (for absolute scaling of ISRF)
4233645a   Jean-Philippe Bernard   improved
86
87
88
89
90
91
92
file=data_dir+use_source_name+'_muse_filters_images'+reso_str+'.sav'
st_info=file_info(file)
IF st_info.exists NE 1 THEN BEGIN
	message,'Could not find '+file,/continue
	stop
ENDIF
restore,file,/verb
14ae4f23   Jean-Philippe Bernard   improved
93
94
95
;% RESTORE: Restored variable: MUSE_IMAGES.
;% RESTORE: Restored variable: MUSE_FILTERS.
;% RESTORE: Restored variable: HREF.
9b37a060   Jean-Philippe Bernard   improved for smoo...
96
;=== needed for all_seds only (for normalisation to Muse)
4233645a   Jean-Philippe Bernard   improved
97
98
99
100
101
102
103
file=data_dir+use_source_name+'_muse_seds_muse_pixels'+reso_str+'.sav'
st_info=file_info(file)
IF st_info.exists NE 1 THEN BEGIN
	message,'Could not find '+file,/continue
	stop
ENDIF
restore,file,/verb
14ae4f23   Jean-Philippe Bernard   improved
104
105
;% RESTORE: Restored variable: ALL_SEDS.
;% RESTORE: Restored variable: ALL_SEDS_INDICES.
ccbd30b1   Jean-Philippe Bernard   First commit
106

de766928   Jean-Philippe Bernard   improved
107
Nvor=max(voronoi_id)+1
ccbd30b1   Jean-Philippe Bernard   First commit
108

ccbd30b1   Jean-Philippe Bernard   First commit
109
110
111
112
113
!quiet=1

t1=systime(0,/sec)
first_vid=0L
lambir=dustem_get_wavelengths(isrf_wavelengths=isrf_wavelengths)
de766928   Jean-Philippe Bernard   improved
114
show_each=100.
ccbd30b1   Jean-Philippe Bernard   First commit
115
116
Nlamb=n_elements(isrf_wavelengths)

14ae4f23   Jean-Philippe Bernard   improved
117
ISRFS=dblarr(Nlamb,Nvor)
eb7ea183   Jean-Philippe Bernard   included stellar ...
118
;Inu_stars=dblarr(Nlamb,Nvor)
14ae4f23   Jean-Philippe Bernard   improved
119
G0s=dblarr(Nvor)
eb7ea183   Jean-Philippe Bernard   included stellar ...
120
;Muse_factors=dblarr(Nvor)
14ae4f23   Jean-Philippe Bernard   improved
121
122
123

;==== get Mathis field for G0 calculations
file=!dustem_soft_dir+'/data/ISRF_MATHIS.DAT'
eb7ea183   Jean-Philippe Bernard   included stellar ...
124
125
126
127
128
st_info=file_info(file)
IF st_info.exists NE 1 THEN BEGIN
	message,'Could not find '+file,/continue
	stop
ENDIF
14ae4f23   Jean-Philippe Bernard   improved
129
130
131
132
readcol,file,Mathis_wavs,Mathis_ISRF
Mathis_ISRF=interpol(Mathis_ISRF,Mathis_wavs,isrf_wavelengths)
Mathis_1mic=interpol(Mathis_ISRF,isrf_wavelengths,1.0)

de766928   Jean-Philippe Bernard   improved
133
134
wavs=dustem_filter2wav(muse_filters[0:2])

ccbd30b1   Jean-Philippe Bernard   First commit
135
136
137
138
FOR vid=first_vid,Nvor-1 DO BEGIN
	IF vid mod show_each EQ 0 THEN BEGIN
		t2=systime(0,/sec)
		delta_t_hr=(t2-t1)/60.^2 ;elapsed time [hr]
de766928   Jean-Philippe Bernard   improved
139
		frac_perc=(1.*vid)/(1.*Nvor)*100.
ccbd30b1   Jean-Philippe Bernard   First commit
140
		delta_t_remain=delta_t_hr/frac_perc*100.-delta_t_hr  ;remaining time [hr]
de766928   Jean-Philippe Bernard   improved
141
142
		message,'done '+strtrim(frac_perc,2)+' % in '+strtrim(delta_t_hr,2)+' hr remaining '+strtrim(delta_t_remain,2)+' hr',/continue
		;stop
ccbd30b1   Jean-Philippe Bernard   First commit
143
144
145
	ENDIF
	;===== get the SSP weights for the given voronoi bins
	weights=phangs_binid2weights(st_muse_weights,vid,st_templates,age_values,metalicity_values,reddening=reddening)
14ae4f23   Jean-Philippe Bernard   improved
146
147
148
	amplitude=1.         ;amplitude is set to 1, and will be corrected by G0 below
	use_reddening=0.     ;This sets Muse reddening to 0. Will be contsrained later
	fpd=phangs_stellar_continuum_plugin_weight2params(weights,parameter_values=val,redenning=use_reddening,/force_include_reddening,amplitude=amplitude,/force_include_amplitude)
8bc14240   Jean-Philippe Bernard   improved
149
150
151
  Nparams=n_elements(val)
  key=intarr(Nparams)
  FOR i=0L,Nparams-1 DO BEGIN
ccbd30b1   Jean-Philippe Bernard   First commit
152
153
154
	    toto=dustem_parameter_description2type(fpd[i],string_name=string_name,key=one_key)
	    key[i]=one_key
 	ENDFOR
14ae4f23   Jean-Philippe Bernard   improved
155
156
157
158
159
 	;==== compute the prediction stellar continuum for comparison to the Muse filter data.
 	;==== Here we use the reddening from MUSE
 	val_sed=val
 	val_sed[1]=reddening   ;for the SED, we use E(B-V)
 	spectrum=dustem_plugin_phangs_stellar_continuum(key=key,val=val_sed)
de766928   Jean-Philippe Bernard   improved
160
161
162
163
164
165
166
 	sed=interpol(spectrum[*,0],lambir,wavs)
 	IF ptr_valid(all_seds[vid]) THEN BEGIN
 		muse_sed=(*all_seds[vid]).stokesI
 	ENDIF ELSE BEGIN
 		muse_sed=sed
 		muse_sed[*]=la_undef()
 	ENDELSE
524e900a   Jean-Philippe Bernard   fixed smoothing I...
167
 	facts=la_div(muse_sed,sed)
14ae4f23   Jean-Philippe Bernard   improved
168
169
170
171
172
 	muse_factor=la_mean(facts)     ;This takes the average value over the MUSE bands
 	;print,G0,reddening
 	;stop
 	val_isrf=val ;for the ISRF, we use E(B-V)=0
 	ISRFS[*,vid]=dustem_plugin_phangs_stellar_isrf(key=key,val=val_isrf,object_distance=object_distance,object_thickness=object_thickness)
524e900a   Jean-Philippe Bernard   fixed smoothing I...
173
174
175
176
177
178
 	;CAUTION with negative values (!!)
 	;IF muse_factor LT 0 THEN BEGIN
 	;	message,'Negative values found',/continue
 	;	stop
 	;ENDIF
 	ISRFS[*,vid]=la_mul(ISRFS[*,vid],muse_factor) ;=== scale the amplitude of ISRFs to the muse data
eb7ea183   Jean-Philippe Bernard   included stellar ...
179
180
 	;Captures Inu_stars
 	Inu_stars[*,vid]=ISRFS[*,vid]
14ae4f23   Jean-Philippe Bernard   improved
181
182
183
 	;=== compute corresponding G0
 	G0=interpol(ISRFS[*,vid],isrf_wavelengths,1.)/Mathis_1mic
 	G0s[vid]=G0
eb7ea183   Jean-Philippe Bernard   included stellar ...
184
 	;Muse_factors[vid]=muse_factor
ccbd30b1   Jean-Philippe Bernard   First commit
185
186
ENDFOR

eb7ea183   Jean-Philippe Bernard   included stellar ...
187
;=== Save the ISRF predictions and ISRF product
ccbd30b1   Jean-Philippe Bernard   First commit
188
IF keyword_set(save) THEN BEGIN
14ae4f23   Jean-Philippe Bernard   improved
189
190
	file_save=data_dir+use_source_name+'_isrf_min_prediction.sav'
	save,ISRFS,G0s,object_distance,object_thickness,use_source_name,file=file_save,/verb
de766928   Jean-Philippe Bernard   improved
191
	message,'Saved '+file_save,/continue
14ae4f23   Jean-Philippe Bernard   improved
192
	phangs_make_isrf_product,use_source_name,voronoi_id,ISRFS,G0s,object_distance,object_thickness
ccbd30b1   Jean-Philippe Bernard   First commit
193
194
ENDIF

eb7ea183   Jean-Philippe Bernard   included stellar ...
195
196
197
198
199
200
201
;=== Save the stellar emission predictions. Inu_stars is already normalized to Muse and is not redenned
;IF keyword_set(save) THEN BEGIN
;	file_save=data_dir+use_source_name+'_stellar_prediction.sav'
;	save,Inu_stars,Muse_factors,file=file_save,/verb
;	message,'Saved '+file_save,/continue
;ENDIF

14ae4f23   Jean-Philippe Bernard   improved
202
203
;cgplot,lindgen(Nvor),G0s,/ylog,yrange=[1.e-5,1],xtit='Voronoi ID',ytit='G0'

de766928   Jean-Philippe Bernard   improved
204
;stop
14ae4f23   Jean-Philippe Bernard   improved
205

ccbd30b1   Jean-Philippe Bernard   First commit
206
207
208
the_end:

END