make_phangs_ssps_isrf_prediction.pro 3.51 KB
PRO make_phangs_ssps_isrf_prediction,source_name=source_name,save=save,help=help

;make_phangs_ssps_isrf_prediction,source_name='ngc0628',/save

;+
; NAME:
;       make_phangs_ssps_isrf_prediction
; CALLING SEQUENCE:
;       make_phangs_ssps_isrf_prediction[,source_name=][,/save]
; PURPOSE:
;       predicts the minimum ISRF in voronoi bins
; 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
;       None
; SIDE EFFECTS:
;       None
; EXAMPLE:
;       make_phangs_ssps_isrf_prediction,/save
; MODIFICATION HISTORY:
;       written by Jean-Philippe Bernard
;-

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

;===== predicts the minimum ISRF in voronoi bins

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
;data_dir='/Volumes/PILOT_FLIGHT1/PHANGS-JWST/DR1/'
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

;IF keyword_set(from_restore) THEN goto,from_restore
;IF keyword_set(from_classes_restore) THEN goto,from_classes_restore

use_source_name='ngc0628'
IF keyword_set(source_name) THEN use_source_name=source_name

CASE use_source_name OF
	'ngc0628':BEGIN
		object_distance=9.84  ;MPc
		object_thickness=0.1  ;kpc
	END
ENDCASE

dustem_define_la_common
obp=[1.1,0,1.15,1]

;dustem_init,show_plots=show_plots
;needed only for NHCO
restore,data_dir+use_source_name+'_jwst_images.sav',/verb
;needed for stellar parameters and voronoi bin info
restore,data_dir+use_source_name+'_muse_images.sav',/verb

Nvor=max(voronoi_id)

use_NHmap=NHCO       ;used NH map in 1.e21 (from CO)

;stop
!quiet=1

t1=systime(0,/sec)
first_vid=0L
lambir=dustem_get_wavelengths(isrf_wavelengths=isrf_wavelengths)
;show_each=10
show_each=100
Nlamb=n_elements(isrf_wavelengths)

ISRFS=fltarr(Nlamb,Nvor)
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]
		frac_perc=vid/Nvor*100
		delta_t_remain=delta_t_hr/frac_perc*100.-delta_t_hr  ;remaining time [hr]
		message,'done '+strtrim(frac_perc)+' % in '+strtrim(delta_t_hr,2)+' hr remaining '+strtrim(delta_t_remain,2)+' hr',/continue
	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)
	amplitude=1.
	reddening=0.     ;This sets Muse reddening to 0. Will be contsrained later
	fpd=phangs_stellar_continuum_plugin_weight2params(weights,parameter_values=val,redenning=reddening,/force_include_reddening,amplitude=amplitude,/force_include_amplitude)
  Nparams=n_elements(val)
  key=intarr(Nparams)
  FOR i=0L,Nparams-1 DO BEGIN
	    toto=dustem_parameter_description2type(fpd[i],string_name=string_name,key=one_key)
	    key[i]=one_key
 	ENDFOR
 	ISRFS[*,vid]=dustem_plugin_phangs_stellar_isrf(key=key,val=val,object_distance=object_distance,object_thickness=object_thickness)
ENDFOR

IF keyword_set(save) THEN BEGIN
	save,ISRFS,object_distance,object_thickness,source_name,file=data_dir+'ngc0628_isrf_min_prediction.sav',/verb
ENDIF

the_end:

END