phangs_smooth_muse_isrf.pro 5.58 KB
PRO phangs_smooth_muse_isrf,source_name $
					       ,resolution_filter=resolution_filter $
					       ,save=save $
					       ,test=test

;+
; 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

dustem_define_la_common
dustem_init

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
restore,file,/verb
;% RESTORE: Restored variable: HREF.

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
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.
file=!phangs_data_dir+'/ISRF/WORK/'+source_name+'_seds_indices.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.

;file=!phangs_data_dir+'/ISRF/WORK/'+source_name+'_all_seds_muse_pixels.sav'
;restore,file,/verb
;% RESTORE: Restored variable: ALL_SEDS.
;% RESTORE: Restored variable: ALL_SEDS_INDICES.

Nwav=(size(ISRFS))[1]
Nvor=(size(ISRFS))[2]

;=== This is to compute the Voronoi bins sizes
vor_num=lonarr(Nvor)
FOR i=0L,Nvor-1 DO BEGIN
	IF ptr_valid(all_seds_indices[i]) THEN BEGIN
		vor_num[i]=n_elements(*all_seds_indices[i])
		IF vor_num[i] EQ 1 THEN BEGIN
			IF *all_seds_indices[i] EQ -1 THEN BEGIN
				vor_num[i]=0L
			ENDIF
	    ENDIF
	ENDIF
ENDFOR
vor_sizes=2.*sqrt(1.*vor_num*sxpar(href,'CDELT2')^2/!pi)   ;FWHM in deg
print,minmax(vor_sizes)*60.^2

;stop
;==== remove negative values in ISRFs
;ind=where(ISRFs LE 0,count)
;IF count NE 0 THEN BEGIN
;	ISRFs[ind]=0.
;ENDIF

;==== Make the ISRF cube
message,'Making the ISRF cube',/info
Nx=sxpar(href,'NAXIS1')
Ny=sxpar(href,'NAXIS2')
ISRF_cube=fltarr(Nx,Ny,Nwav)+la_undef()

im0=ISRF_cube[*,*,0]
ISRF0=fltarr(Nwav)+la_undef()
FOR i=0L,Nvor-1 DO BEGIN
	IF i mod 1000 EQ 0 THEN BEGIN
		message,strtrim(1.*i/Nvor*100,2)+' %',/continue
		;stop
	ENDIF
	IF vor_num[i] NE 0 THEN BEGIN
		ij=index2ij(*all_seds_indices[i],[Nx,Ny])
		FOR j=0L,vor_num[i]-1 DO ISRF_cube[ij[j,0],ij[j,1],*]=ISRFS[*,i]
	ENDIF
ENDFOR

;==== smooth the ISRF
use_reso_filter='SPIRE3'
IF keyword_set(resolution_filter) THEN use_reso_filter=resolution_filter

message,'smoothing the ISRF cube',/info
data_reso=3./60./60.
reso_str='_'+use_reso_filter
final_reso=dustem_filter2reso(use_reso_filter)

;stop
;in fact degrade_res can degrade resolution of cubes, so ...
;=== That's a test
IF keyword_set(test) THEN BEGIN
	ISRFs=degrade_res(ISRF_cube[*,*,0:2],href,data_reso,final_reso,hout)
	test_str='Test'
ENDIF ELSE BEGIN
	ISRFs=degrade_res(ISRF_cube,href,data_reso,final_reso,hout)
	test_str=''
ENDELSE
header=hout
;stop

;=== project ISRFs on reference header for given resolution
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
restore,file,/verb
;stop

NNx=sxpar(href,'NAXIS1')
NNy=sxpar(href,'NAXIS2')
proj_ISRFs=fltarr(NNx,NNy,Nwav)
i=0L
proj_ISRFs[*,*,i]=project2(header,ISRFs[*,*,i],href,/silent)
;FOR i=1L,Nwav-1 DO BEGIN
FOR i=1L,(size(ISRFs))[3]-1 DO BEGIN
	proj_ISRFs[*,*,i]=project2(header,ISRFs[*,*,i],href,/previous_lut,/silent)
ENDFOR

;stop
;==== put back ISRFs on voronoi bins
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
;% 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.
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
		ij=index2ij(ind,[NNx,NNy])
		out_ISRFS[*,i]=reform(proj_ISRFs[ij[0,0],ij[0,1],*])
	ENDELSE
ENDFOR
;ISRFs=proj_ISRFs
ISRFs=out_ISRFs

IF keyword_set(save) THEN BEGIN
	file_save=!phangs_data_dir+'/ISRF/WORK/'+test_str+source_name+'_isrf_min_prediction'+reso_str+'.sav' 
	save,ISRFs,href,use_reso_filter,file=file_save
	message,'Saved '+file_save,/continue
ENDIF

the_end:
;stop

END