Blame view

LabTools/IRAP/JPB/phangs_smooth_muse_isrf.pro 9.28 KB
9b0b6d7e   Jean-Philippe Bernard   finished implemen...
1
2
3
PRO phangs_smooth_muse_isrf,source_name $
					       ,resolution_filter=resolution_filter $
					       ,save=save $
524e900a   Jean-Philippe Bernard   fixed smoothing I...
4
5
					       ,show_plots=show_plots $
					       ,nostop=nostop $
9b0b6d7e   Jean-Philippe Bernard   finished implemen...
6
					       ,test=test
26556ecf   Jean-Philippe Bernard   First commit
7

9b0b6d7e   Jean-Philippe Bernard   finished implemen...
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
;+
; NAME:
;    phangs_smooth_muse_isrf
; PURPOSE:
;    Smoothes ISRF to a given resolution
; CATEGORY:
;    PHANGS ISRF
; CALLING SEQUENCE:
;    phangs_smooth_muse_isrf,source_name[,resolution_filter=][,/save][,/test]=
; INPUTS:
;    source_name            : source name
; OPTIONAL INPUT PARAMETERS:
;    resolution_filter      :resolution of the filter to be used for smoothing (defaults=)
; OUTPUTS:
;    None
; OPTIONAL OUTPUT PARAMETERS:
;    None
; ACCEPTED KEY-WORDS:
;    save      = If set, saves results
;    help      = If set, print this help
; COMMON BLOCKS:
;    None
; SIDE EFFECTS:
;    The following files are written, if they do not already exist:
;    _isrf_min_prediction_*.sav
; RESTRICTIONS:
;    None
; PROCEDURE:
;    
; EXAMPLES
;	phangs_smooth_muse_isrf,'ngc0628',reso_filter='SPIRE3'
; MODIFICATION HISTORY:
;    Written by J.-Ph. Bernard (2023)
;    Evolution details on the DustEMWrap gitlab.
;    See http://dustemwrap.irap.omp.eu/ for FAQ and help.  
;-

IF keyword_set(help) THEN BEGIN
  doc_library,'phangs_smooth_muse_isrf'
  goto,the_end
ENDIF
26556ecf   Jean-Philippe Bernard   First commit
49
50
51

dustem_define_la_common
dustem_init
524e900a   Jean-Philippe Bernard   fixed smoothing I...
52
53
54
obp=[1.1,0,1.15,1]
imrange=[-0.1,1]*1.e-19  ;image range for ISRF images
win=0L
26556ecf   Jean-Philippe Bernard   First commit
55

524e900a   Jean-Philippe Bernard   fixed smoothing I...
56
57
58
59
60
61
62
IF keyword_set(test) THEN BEGIN
  nwav_ref=1
ENDIF ELSE BEGIN
	nwav_ref=101
ENDELSE

;========= Restore informations at initial resolution
8cfdf0b6   Jean-Philippe Bernard   improved
63
64
65
66
67
68
file=!phangs_data_dir+'/ISRF/WORK/'+source_name+'_ref_header.sav'
st_info=file_info(file)
IF st_info.exists NE 1 THEN BEGIN
	message,'Could not find '+file,/continue
	stop
ENDIF
26556ecf   Jean-Philippe Bernard   First commit
69
70
restore,file,/verb
;% RESTORE: Restored variable: HREF.
524e900a   Jean-Philippe Bernard   fixed smoothing I...
71
href0=href & href=0
26556ecf   Jean-Philippe Bernard   First commit
72

8cfdf0b6   Jean-Philippe Bernard   improved
73
74
75
76
77
78
file=!phangs_data_dir+'/ISRF/WORK/'+source_name+'_isrf_min_prediction.sav'
st_info=file_info(file)
IF st_info.exists NE 1 THEN BEGIN
	message,'Could not find '+file,/continue
	stop
ENDIF
26556ecf   Jean-Philippe Bernard   First commit
79
80
81
82
83
84
restore,file,/verb
;% RESTORE: Restored variable: ISRFS.
;% RESTORE: Restored variable: G0S.
;% RESTORE: Restored variable: OBJECT_DISTANCE.
;% RESTORE: Restored variable: OBJECT_THICKNESS.
;% RESTORE: Restored variable: USE_SOURCE_NAME.
524e900a   Jean-Philippe Bernard   fixed smoothing I...
85
86
87
88
89
90
ISRFS0=ISRFS & ISRFS=0
G0S0=G0S & G0s=0
;=== remove negative ISRFs values
ind=where(ISRFS0 LT 0 AND ISRFS0 NE la_undef(),count)
IF count NE 0 THEN ISRFS0[ind]=0.

9b0b6d7e   Jean-Philippe Bernard   finished implemen...
91
file=!phangs_data_dir+'/ISRF/WORK/'+source_name+'_seds_indices.sav'
8cfdf0b6   Jean-Philippe Bernard   improved
92
93
94
95
96
st_info=file_info(file)
IF st_info.exists NE 1 THEN BEGIN
	message,'Could not find '+file,/continue
	stop
ENDIF
26556ecf   Jean-Philippe Bernard   First commit
97
restore,file,/verb
9b0b6d7e   Jean-Philippe Bernard   finished implemen...
98
;% RESTORE: Restored variable: ALL_SEDS_INDICES.
524e900a   Jean-Philippe Bernard   fixed smoothing I...
99
100
101
102
ALL_SEDS_INDICES0=ALL_SEDS_INDICES & ALL_SEDS_INDICES=0

Nwav=(size(ISRFS0))[1]
Nvor=(size(ISRFS0))[2]
9b0b6d7e   Jean-Philippe Bernard   finished implemen...
103

524e900a   Jean-Philippe Bernard   fixed smoothing I...
104
vors0=lindgen(Nvor)  ;for plots only
33d0e4eb   Jean-Philippe Bernard   improved
105

524e900a   Jean-Philippe Bernard   fixed smoothing I...
106
;=== This is to compute the Voronoi bins sizes (not used later)
26556ecf   Jean-Philippe Bernard   First commit
107
108
vor_num=lonarr(Nvor)
FOR i=0L,Nvor-1 DO BEGIN
524e900a   Jean-Philippe Bernard   fixed smoothing I...
109
110
	IF ptr_valid(all_seds_indices0[i]) THEN BEGIN
		vor_num[i]=n_elements(*all_seds_indices0[i])
9b0b6d7e   Jean-Philippe Bernard   finished implemen...
111
		IF vor_num[i] EQ 1 THEN BEGIN
524e900a   Jean-Philippe Bernard   fixed smoothing I...
112
			IF *all_seds_indices0[i] EQ -1 THEN BEGIN
9b0b6d7e   Jean-Philippe Bernard   finished implemen...
113
114
				vor_num[i]=0L
			ENDIF
524e900a   Jean-Philippe Bernard   fixed smoothing I...
115
	  ENDIF
9b0b6d7e   Jean-Philippe Bernard   finished implemen...
116
	ENDIF
26556ecf   Jean-Philippe Bernard   First commit
117
ENDFOR
524e900a   Jean-Philippe Bernard   fixed smoothing I...
118
vor_sizes=2.*sqrt(1.*vor_num*sxpar(href0,'CDELT2')^2/!pi)   ;FWHM in deg
33d0e4eb   Jean-Philippe Bernard   improved
119
print,minmax(vor_sizes)*60.^2
26556ecf   Jean-Philippe Bernard   First commit
120

33d0e4eb   Jean-Philippe Bernard   improved
121
;==== Make the ISRF cube
524e900a   Jean-Philippe Bernard   fixed smoothing I...
122
123
124
125
message,'Making the ISRF cube at initial resolution',/info
Nx=sxpar(href0,'NAXIS1')
Ny=sxpar(href0,'NAXIS2')
ISRF_cube0=fltarr(Nx,Ny,Nwav)+la_undef()
26556ecf   Jean-Philippe Bernard   First commit
126

524e900a   Jean-Philippe Bernard   fixed smoothing I...
127
128
im0=ISRF_cube0[*,*,0]
;ISRF0=fltarr(Nwav)+la_undef()
26556ecf   Jean-Philippe Bernard   First commit
129
FOR i=0L,Nvor-1 DO BEGIN
33d0e4eb   Jean-Philippe Bernard   improved
130
131
132
133
	IF i mod 1000 EQ 0 THEN BEGIN
		message,strtrim(1.*i/Nvor*100,2)+' %',/continue
		;stop
	ENDIF
26556ecf   Jean-Philippe Bernard   First commit
134
	IF vor_num[i] NE 0 THEN BEGIN
524e900a   Jean-Philippe Bernard   fixed smoothing I...
135
136
		ij=index2ij(*all_seds_indices0[i],[Nx,Ny])
		FOR j=0L,vor_num[i]-1 DO ISRF_cube0[ij[j,0],ij[j,1],*]=ISRFS0[*,i]
26556ecf   Jean-Philippe Bernard   First commit
137
138
139
	ENDIF
ENDFOR

524e900a   Jean-Philippe Bernard   fixed smoothing I...
140
141
142
143
144
145
146
IF keyword_set(show_plots) THEN BEGIN
	window,win & win=win+1
	tit='initial ISRF'
	image_cont20,ISRF_CUBE0[*,*,101],href0,/square,/silent,imrange=imrange,image_color_table='jpbloadct',axis_color_table=1,off_bar_pos=obp,tit=tit
ENDIF
IF not keyword_set(nostop) THEN stop

33d0e4eb   Jean-Philippe Bernard   improved
147
148
;==== smooth the ISRF
use_reso_filter='SPIRE3'
9b0b6d7e   Jean-Philippe Bernard   finished implemen...
149
IF keyword_set(resolution_filter) THEN use_reso_filter=resolution_filter
26556ecf   Jean-Philippe Bernard   First commit
150

33d0e4eb   Jean-Philippe Bernard   improved
151
152
message,'smoothing the ISRF cube',/info
data_reso=3./60./60.
9b0b6d7e   Jean-Philippe Bernard   finished implemen...
153
reso_str='_'+use_reso_filter
33d0e4eb   Jean-Philippe Bernard   improved
154
final_reso=dustem_filter2reso(use_reso_filter)
26556ecf   Jean-Philippe Bernard   First commit
155

33d0e4eb   Jean-Philippe Bernard   improved
156
157
158
;stop
;in fact degrade_res can degrade resolution of cubes, so ...
;=== That's a test
524e900a   Jean-Philippe Bernard   fixed smoothing I...
159
;goto,jump_there
33d0e4eb   Jean-Philippe Bernard   improved
160
IF keyword_set(test) THEN BEGIN
524e900a   Jean-Philippe Bernard   fixed smoothing I...
161
	ISRF_cube=degrade_res(ISRF_cube0[*,*,100:102],href0,data_reso,final_reso,hout)
bbfe2364   Jean-Philippe Bernard   fixed a bug
162
	test_str='Test'
524e900a   Jean-Philippe Bernard   fixed smoothing I...
163
	Nwav=3
33d0e4eb   Jean-Philippe Bernard   improved
164
ENDIF ELSE BEGIN
524e900a   Jean-Philippe Bernard   fixed smoothing I...
165
	ISRF_cube=degrade_res(ISRF_cube0,href0,data_reso,final_reso,hout)
bbfe2364   Jean-Philippe Bernard   fixed a bug
166
	test_str=''
33d0e4eb   Jean-Philippe Bernard   improved
167
168
ENDELSE
header=hout
524e900a   Jean-Philippe Bernard   fixed smoothing I...
169
170
171
172
goto,jump_there2

jump_there:
bidon=degrade_res(ISRF_cube0[*,*,0],href0,data_reso,final_reso,hout,/no_resample,FT_PSF=psf_FT)
33d0e4eb   Jean-Philippe Bernard   improved
173
;stop
524e900a   Jean-Philippe Bernard   fixed smoothing I...
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
ISRF_cube=fltarr(sxpar(hout,'NAXIS1'),sxpar(hout,'NAXIS2'),Nwav)
IF keyword_set(test) THEN BEGIN
	FOR k=100,102 DO BEGIN
		ISRF_cube[*,*,k-100]=degrade_res(ISRF_cube0[*,*,k],href0,data_reso,final_reso,hout,/no_resample,FT_PSF=psf_FT)
	ENDFOR
	test_str='Test'
	Nwav=3
ENDIF ELSE BEGIN
	FOR k=0L,Nwav-1 DO BEGIN
		message,'Degrading ISRF plane '+strtrim(k,2)+' / '+strtrim(Nwav,2),/info
		res=degrade_res(ISRF_cube0[*,*,k],href0,data_reso,final_reso,hout,/no_resample,FT_PSF=psf_FT)
		ISRF_cube[*,*,k]=res
	ENDFOR
	test_str=''
ENDELSE
header=hout

jump_there2:

IF keyword_set(show_plots) THEN BEGIN
	window,win & win=win+1
	tit='Smoothed ISRF'
	IF keyword_set(test) THEN BEGIN
		image_cont20,ISRF_CUBE[*,*,1],header,/square,/silent,imrange=imrange,image_color_table='jpbloadct',axis_color_table=1,off_bar_pos=obp,tit=tit
	ENDIF ELSE BEGIN
		image_cont20,ISRF_CUBE[*,*,101],header,/square,/silent,imrange=imrange,image_color_table='jpbloadct',axis_color_table=1,off_bar_pos=obp,tit=tit
	ENDELSE
ENDIF

IF not keyword_set(nostop) THEN stop
26556ecf   Jean-Philippe Bernard   First commit
204

524e900a   Jean-Philippe Bernard   fixed smoothing I...
205
206
;=== project ISRFs on reference header for the given resolution
message,'project smoothed ISRF cube on reference header',/info
8cfdf0b6   Jean-Philippe Bernard   improved
207
208
209
210
211
212
file=!phangs_data_dir+'/ISRF/WORK/'+source_name+'_ref_header'+reso_str+'.sav'
st_info=file_info(file)
IF st_info.exists NE 1 THEN BEGIN
	message,'Could not find '+file,/continue
	stop
ENDIF
9b0b6d7e   Jean-Philippe Bernard   finished implemen...
213
restore,file,/verb
524e900a   Jean-Philippe Bernard   fixed smoothing I...
214
;% RESTORE: Restored variable: HREF.
9b0b6d7e   Jean-Philippe Bernard   finished implemen...
215
216
217
218
;stop

NNx=sxpar(href,'NAXIS1')
NNy=sxpar(href,'NAXIS2')
524e900a   Jean-Philippe Bernard   fixed smoothing I...
219
proj_ISRF_cube=fltarr(NNx,NNy,Nwav)
9b0b6d7e   Jean-Philippe Bernard   finished implemen...
220
i=0L
524e900a   Jean-Philippe Bernard   fixed smoothing I...
221
proj_ISRF_cube[*,*,i]=project2(header,ISRF_cube[*,*,i],href,/silent)
9b0b6d7e   Jean-Philippe Bernard   finished implemen...
222
;FOR i=1L,Nwav-1 DO BEGIN
524e900a   Jean-Philippe Bernard   fixed smoothing I...
223
224
FOR i=1L,(size(proj_ISRF_CUBE))[3]-1 DO BEGIN
	proj_ISRF_cube[*,*,i]=project2(header,ISRF_CUBE[*,*,i],href,/previous_lut,/silent)
9b0b6d7e   Jean-Philippe Bernard   finished implemen...
225
226
ENDFOR

524e900a   Jean-Philippe Bernard   fixed smoothing I...
227
228
229
230
231
232
233
234
235
236
237
238
IF keyword_set(show_plots) THEN BEGIN
	window,win & win=win+1
	tit='Projected ISRF'
	IF keyword_set(test) THEN BEGIN
		image_cont20,proj_ISRF_CUBE[*,*,1],href,/square,/silent,imrange=imrange,image_color_table='jpbloadct',axis_color_table=1,off_bar_pos=obp,tit=tit
	ENDIF ELSE BEGIN
		image_cont20,proj_ISRF_CUBE[*,*,101],href,/square,/silent,imrange=imrange,image_color_table='jpbloadct',axis_color_table=1,off_bar_pos=obp,tit=tit
	ENDELSE
ENDIF

IF not keyword_set(nostop) THEN stop

9b0b6d7e   Jean-Philippe Bernard   finished implemen...
239
;==== put back ISRFs on voronoi bins
524e900a   Jean-Philippe Bernard   fixed smoothing I...
240
message,'putting back ISRFs on voronoi bins',/info
8cfdf0b6   Jean-Philippe Bernard   improved
241
242
243
244
245
246
247
file=!phangs_data_dir+'/ISRF/WORK/'+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
9b0b6d7e   Jean-Philippe Bernard   finished implemen...
248
249
250
251
252
253
254
;% 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.
524e900a   Jean-Philippe Bernard   fixed smoothing I...
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
file=!phangs_data_dir+'/ISRF/WORK/'+use_source_name+'_seds_indices'+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
;% RESTORE: Restored variable: ALL_SEDS_INDICES.

IF keyword_set(show_plots) THEN BEGIN
	tit='Voronoi ID'
	window,win & win=win+1
	image_cont20,VORONOI_ID,href,/square,/silent,image_color_table='jpbloadct',axis_color_table=1,off_bar_pos=obp,tit=tit
ENDIF

9b0b6d7e   Jean-Philippe Bernard   finished implemen...
270
271
272
273
274
275
276
277
NNvor=max(voronoi_id)+1
out_ISRFS=fltarr(Nwav,NNvor)
FOR i=0L,NNvor-1 DO BEGIN
	ind=where(voronoi_id EQ i,count)
	IF count NE 1 THEN BEGIN
		message,'count should be 1',/continue
		stop
	ENDIF ELSE BEGIN
524e900a   Jean-Philippe Bernard   fixed smoothing I...
278
279
280
281
282
283
		;ij=index2ij(ind,[NNx,NNy])
		ij2=index2ij(*all_seds_indices[i],[NNx,NNy])
    ;IF ij[0,0] NE ij2[0,0] OR ij[0,1] NE ij2[0,1] THEN stop
		out_ISRFS[*,i]=reform(proj_ISRF_cube[ij2[0,0],ij2[0,1],*])
		;ind=where(out_ISRFS[*,i] GT 1.e-14,count)
		;IF count NE 0 THEN stop
9b0b6d7e   Jean-Philippe Bernard   finished implemen...
284
285
	ENDELSE
ENDFOR
524e900a   Jean-Philippe Bernard   fixed smoothing I...
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313

vors=lindgen(NNvor)  ;for plots only

IF keyword_set(show_plots) THEN BEGIN
	window,win & win=win+1
	!p.multi=[0,1,2]
	indok=where(ISRFS0[100,*] NE la_undef())
	cgplot,vors0[indok],ISRFS0[101,indok],/ylog
	IF keyword_set(test) THEN BEGIN
		cgplot,vors,out_ISRFS[1,*],/ylog
	ENDIF ELSE BEGIN
		cgplot,vors,out_ISRFS[101,*],/ylog
	ENDELSE
ENDIF

;stop

IF not keyword_set(nostop) THEN stop

;print,la_min(ISRFS0),la_max(ISRFS0)
;  -2.0413261e-21   1.6803689e-16
;print,la_min(ISRF_cube),la_max(ISRF_cube)
; -1.48842e-10  1.52286e-10
;print,la_min(proj_ISRF_cube),la_max(proj_ISRF_cube)
; -1.48842e-10  1.52286e-10
;print,la_min(OUT_ISRFS),la_max(OUT_ISRFS)
; -1.48842e-10  1.52286e-10

9b0b6d7e   Jean-Philippe Bernard   finished implemen...
314
315
316
;ISRFs=proj_ISRFs
ISRFs=out_ISRFs

33d0e4eb   Jean-Philippe Bernard   improved
317
318
IF keyword_set(save) THEN BEGIN
	file_save=!phangs_data_dir+'/ISRF/WORK/'+test_str+source_name+'_isrf_min_prediction'+reso_str+'.sav' 
9b0b6d7e   Jean-Philippe Bernard   finished implemen...
319
	save,ISRFs,href,use_reso_filter,file=file_save
33d0e4eb   Jean-Philippe Bernard   improved
320
321
	message,'Saved '+file_save,/continue
ENDIF
26556ecf   Jean-Philippe Bernard   First commit
322

9b0b6d7e   Jean-Philippe Bernard   finished implemen...
323
324
the_end:
;stop
26556ecf   Jean-Philippe Bernard   First commit
325
326

END