Blame view

src/idl/dustem_plot_fit_sed.pro 13.4 KB
452c334e   Ilyes Choubani   Implementation Of...
1
2
 PRO dustem_plot_fit_sed,st,sed, $
                         res=res,errors=errors,chi2=chi2,rchi2=rchi2, $
759a527d   Ilyes Choubani   general update
3
                         no_spec_error=no_spec_error,title=title,$;xtit=xtit,ytit=ytit,xr=xr,yr=yr $
452c334e   Ilyes Choubani   Implementation Of...
4
5
6
                         help=help,win=win,ps=ps, $
                         legend_xpos=legend_xpos,legend_ypos=legend_ypos,legend_offset=legend_offset, $
                         _extra=_extra
427f1205   Jean-Michel Glorian   version 4.2 merged
7

427f1205   Jean-Michel Glorian   version 4.2 merged
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:
;    dustem_plot_fit_sed
; PURPOSE:
;    Plots a Dustem model and SED. Parameter values and error are
;    printed on plot. Used for plotting results during fit.
; CATEGORY:
;    Dustem
; CALLING SEQUENCE:
;    dustem_plot_fit_sed,st,sed,cont[,/no_spec_error][,res=][,errors=][,chi2=][,rchi2=][/help][_extra=]
; INPUTS:
;    st        = Dustem model output structure
;    sed       = Dustem model SED
;    cont      = Dustem model NIR continuum
; OPTIONAL INPUT PARAMETERS:
;    res       = fit result values. If set values are written on plot.
;    errors    = fit result errors. If set values are written on plot.
;    chi2      = fit chi^2. if set value is written on plot.
;    rchi2     = Reduced fit chi^2. if set value is written on plot.
;    _extra    = extra parameters for the plot routine
; OUTPUTS:
;    None
; OPTIONAL OUTPUT PARAMETERS:
;    None
; ACCEPTED KEY-WORDS:
;    help      = If set, print this help
; COMMON BLOCKS:
;    None
; SIDE EFFECTS:
;    SED and model are plotted
; RESTRICTIONS:
;    The dustem idl wrapper must be installed
; PROCEDURE:
;    None
; EXAMPLES
;    dustem_plot_fit_sed,st,sed,cont
; MODIFICATION HISTORY:
;    Written by J.-Ph. Bernard
;    see evolution details on the dustem cvs maintained at CESR
;    Contact J.-Ph. Bernard (Jean-Philippe.Bernard@cesr.fr) in case of problems.
;-

9ccf7615   Jean-Philippe Bernard   modified to fit u...
49
50
;stop

427f1205   Jean-Michel Glorian   version 4.2 merged
51
52
53
54
55
IF keyword_set(help) THEN BEGIN
  doc_library,'dustem_plot_fit_sed'
  goto,the_end
ENDIF

9ccf7615   Jean-Philippe Bernard   modified to fit u...
56
IF keyword_set(ps) THEN BEGIN
452c334e   Ilyes Choubani   Implementation Of...
57
    set_plot, 'PS'
b0cabd3c   Ilyes Choubani   general update
58
    device, filename=ps, /color,set_character_size=[170,250], /encapsulated
452c334e   Ilyes Choubani   Implementation Of...
59
ENDIF ELSE BEGIN
4750086c   Ilyes Choubani   nouvelle philosph...
60

452c334e   Ilyes Choubani   Implementation Of...
61
62
63
  set_plot,'X'
    IF keyword_set(win) then window,win
ENDELSE
427f1205   Jean-Michel Glorian   version 4.2 merged
64

759a527d   Ilyes Choubani   general update
65
fact = 1.e4*(*!dustem_HCD)/(4.*!pi)/(3.e8/1.e-6/st.sed.wav)*1.e20/1.e7
427f1205   Jean-Michel Glorian   version 4.2 merged
66

9ccf7615   Jean-Philippe Bernard   modified to fit u...
67
68
69
;use_col_data_filt=70
;use_col_sed_spec=170
use_col_data_filt='blue'
9be94157   Jean-Philippe Bernard   improved
70
71
;use_col_sed_spec='red'
use_col_sed_spec='grey'
427f1205   Jean-Michel Glorian   version 4.2 merged
72
IF not keyword_set(col_sed) THEN BEGIN
9ccf7615   Jean-Philippe Bernard   modified to fit u...
73
74
  ;use_col_sed_filt=250     ;red
  use_col_sed_filt='red'     ;red
427f1205   Jean-Michel Glorian   version 4.2 merged
75
76
77
78
ENDIF ELSE BEGIN
  use_col_sed_filt=col_sed
ENDELSE
IF not keyword_set(col_tot) THEN BEGIN
9ccf7615   Jean-Philippe Bernard   modified to fit u...
79
80
  ;use_col_tot=200
  use_col_tot='black'
427f1205   Jean-Michel Glorian   version 4.2 merged
81
82
83
84
85
86
87
88
ENDIF ELSE BEGIN
  use_col_tot=col_tot
ENDELSE
IF not keyword_set(line_tot) THEN BEGIN
  use_line_tot=0
ENDIF ELSE BEGIN
  use_line_tot=line_tot
ENDELSE
427f1205   Jean-Michel Glorian   version 4.2 merged
89

452c334e   Ilyes Choubani   Implementation Of...
90

427f1205   Jean-Michel Glorian   version 4.2 merged
91
spec = st.sed.em_tot * fact
452c334e   Ilyes Choubani   Implementation Of...
92
93
94

;ADDING PLUGIN(S) TO SPECTRUM----------------
;if n_tags(!dustem_data.sed) gt 1 then begin 
79991f38   Jean-Philippe Bernard   fixed for whan sc...
95
96
scopes=tag_names((*!dustem_scope))
IF scopes[0] NE 'NONE' THEN BEGIN
759a527d   Ilyes Choubani   general update
97
;IF ptr_valid(!dustem_plugin) THEN BEGIN
79991f38   Jean-Philippe Bernard   fixed for whan sc...
98
99
100
101
  FOR i=0L,n_tags(*!dustem_scope)-1 DO BEGIN
    IF total(strsplit((*(*!dustem_scope).(i)),'+',/extract) EQ 'ADD_SED') THEN spec+=(*(*!dustem_plugin).(i))[*,0]
  ENDFOR
ENDIF
452c334e   Ilyes Choubani   Implementation Of...
102
103
;endif
;------------------------------------------
427f1205   Jean-Michel Glorian   version 4.2 merged
104

6730c3f8   Jean-Philippe Bernard   modified to be co...
105
106
;stop

427f1205   Jean-Michel Glorian   version 4.2 merged
107
108
;use_cols=[use_col_pah,use_col_vsg,use_col_bg,use_col_cont]
;use_lines=[use_line_pah,use_line_vsg,use_line_bg,use_line_cont]
4750086c   Ilyes Choubani   nouvelle philosph...
109
;col_off=30
6730c3f8   Jean-Philippe Bernard   modified to be co...
110
111
;Ngrains=(*!dustem_params).grain.Ngrains
Ngrains=(*!dustem_params).Ngrains
9ccf7615   Jean-Philippe Bernard   modified to fit u...
112
113
;use_cols=long(findgen(Ngrains)/(Ngrains-1)*(255-col_off)+col_off)
use_cols=dustem_grains_colors(Ngrains,/cgplot)
9ccf7615   Jean-Philippe Bernard   modified to fit u...
114
115
116
117
use_lines=replicate(0,Ngrains)

norm = sed * 0. + 1

389a2b1d   Jean-Philippe Bernard   improved
118
;====== PLOT THE SED
4750086c   Ilyes Choubani   nouvelle philosph...
119
120
121

IF keyword_set(title) THEN title = title ELSE title = 'Spectral Energy Distribution (Running)'

759a527d   Ilyes Choubani   general update
122
123
124
125
126
127
128
129
IF keyword_set(xr) THEN xr = xr ELSE xr = [1.00E+00,6.00E+04]

IF keyword_set(yr) THEN yr = yr ELSE yr = [1.00E-7,5.00E03]

IF keyword_set(xtit) THEN xtit = xtit ELSE xtit = textoidl('\lambda (\mum)')

IF keyword_set(ytit) THEN ytit = ytit ELSE ytit = textoidl('Brightness/N_H (MJy/sr/H)')

4750086c   Ilyes Choubani   nouvelle philosph...
130
131
;deffo define a title variable here. The procedures are not communicating with each other. 

1fa79b40   Jean-Philippe Bernard   added back passin...
132
;cgplot,(*!dustem_data.sed).wav,(*!dustem_data.sed).values/norm,/nodata,xtit='',ytit=textoidl('Brightness/N_H (MJy/sr/H)'),tit=title,ylog=1,/xlog,xr=xr,yr=yr,/ys,/xs,position=[0.12,0.35,0.96,0.90],xtickformat='(A1)'
759a527d   Ilyes Choubani   general update
133
cgplot,(*!dustem_data.sed).wav,(*!dustem_data.sed).values/norm,/nodata,xtit='',ytit=ytit,tit=title,/ylog,/xlog,/ys,/xs,position=[0.12,0.35,0.96,0.90],xtickformat='(A1)',_extra=_extra,charsize=1.3
452c334e   Ilyes Choubani   Implementation Of...
134
135
136
137
138
139
140


;cgplot,st.polsed.wav,Q_sed*fact,xtit='',ytit=ytitstq,tit=titstq,ylog=ylog,/xlog,xr=xr,yr=yr,/ys,/xs,position=[0.17,0.35,0.95,0.95],xtickformat='(A1)'

;this is where you will add the normalized sed


427f1205   Jean-Michel Glorian   version 4.2 merged
141
142
143
144
145
ind_filt=where((*!dustem_data.sed).filt_names NE 'SPECTRUM',count_filt)
ind_spec=where((*!dustem_data.sed).filt_names EQ 'SPECTRUM',count_spec)
;=== Plot the data
IF count_spec NE 0 THEN BEGIN
  plotsym,0,/fill
9ccf7615   Jean-Philippe Bernard   modified to fit u...
146
147
148
  xx=((*!dustem_data.sed).wav)[ind_spec]
  yy=((*!dustem_data.sed).values)[ind_spec]/norm[ind_spec]
  rms=3.*((*!dustem_data.sed).sigma)[ind_spec]/2./norm[ind_spec]
452c334e   Ilyes Choubani   Implementation Of...
149
  cgoplot,xx,yy,psym=8,syms=0.5,color=use_col_sed_spec
427f1205   Jean-Michel Glorian   version 4.2 merged
150
  IF not keyword_set(no_spec_error) THEN BEGIN
9be94157   Jean-Philippe Bernard   improved
151
    cgerrplot,xx,yy-rms,yy+rms,color=use_col_sed_spec
9ccf7615   Jean-Philippe Bernard   modified to fit u...
152
    ;err_bar,((*!dustem_data.sed).wav)(ind_spec),((*!dustem_data.sed).values)(ind_spec)/norm(ind_spec),yrms=3.*((*!dustem_data.sed).sigma)(ind_spec)/2./norm(ind_spec)
427f1205   Jean-Michel Glorian   version 4.2 merged
153
154
155
  ENDIF
ENDIF
IF count_filt NE 0 THEN BEGIN
b5ccb706   Jean-Philippe Bernard   improved to fit p...
156
  ;stop
9ccf7615   Jean-Philippe Bernard   modified to fit u...
157
158
159
  xx=((*!dustem_data.sed).wav)[ind_filt]
  yy=((*!dustem_data.sed).values)[ind_filt]/norm[ind_filt]
  rms=3.*((*!dustem_data.sed).sigma)[ind_filt]/2./norm[ind_filt]
427f1205   Jean-Michel Glorian   version 4.2 merged
160
  plotsym,0,/fill
452c334e   Ilyes Choubani   Implementation Of...
161
  cgoplot,xx,yy,psym=8,color='Dodger Blue';use_col_data_filt
9ccf7615   Jean-Philippe Bernard   modified to fit u...
162
  ;err_bar,((*!dustem_data.sed).wav)(ind_filt),((*!dustem_data.sed).values)(ind_filt)/norm(ind_filt),yrms=3.*((*!dustem_data.sed).sigma)(ind_filt)/2./norm(ind_filt),color=use_col_data_filt
452c334e   Ilyes Choubani   Implementation Of...
163
  cgerrplot,xx,yy-rms,yy+rms,color='Dodger Blue';use_col_data_filt
427f1205   Jean-Michel Glorian   version 4.2 merged
164
165
166
167
ENDIF
;=== Plot the computed SED
IF count_filt NE 0 THEN BEGIN
  plotsym,8
9ccf7615   Jean-Philippe Bernard   modified to fit u...
168
169
  xx=((*!dustem_data.sed).wav)[ind_filt]
  yy=sed[ind_filt]/norm[ind_filt]
dc72d0b6   Ilyes Choubani   initial procedure...
170
  cgoplot,xx,yy,color=use_col_sed_filt,psym=6,syms=2
427f1205   Jean-Michel Glorian   version 4.2 merged
171
172
173
ENDIF
IF count_spec NE 0 THEN BEGIN
  plotsym,0
9ccf7615   Jean-Philippe Bernard   modified to fit u...
174
175
  xx=((*!dustem_data.sed).wav)[ind_spec]
  yy=sed[ind_spec]/norm[ind_spec]
dc72d0b6   Ilyes Choubani   initial procedure...
176
  cgoplot,xx,yy,color=use_col_sed_filt,psym=6,syms=2
427f1205   Jean-Michel Glorian   version 4.2 merged
177
178
179
ENDIF


9ccf7615   Jean-Philippe Bernard   modified to fit u...
180
IF !dustem_show_plot EQ 2 THEN BEGIN
427f1205   Jean-Michel Glorian   version 4.2 merged
181
	norm = spec
9ccf7615   Jean-Philippe Bernard   modified to fit u...
182
ENDIF ELSE BEGIN
427f1205   Jean-Michel Glorian   version 4.2 merged
183
	norm = spec * 0. + 1
9ccf7615   Jean-Philippe Bernard   modified to fit u...
184
ENDELSE
427f1205   Jean-Michel Glorian   version 4.2 merged
185
FOR i=0L,Ngrains-1 DO BEGIN
b0cabd3c   Ilyes Choubani   general update
186
  use_cols[1]='Cornflower'
9ccf7615   Jean-Philippe Bernard   modified to fit u...
187
  cgoplot,st.sed.wav,st.sed.(i+1)*fact/norm,color=use_cols[i],linestyle=use_lines[i]
427f1205   Jean-Michel Glorian   version 4.2 merged
188
ENDFOR
452c334e   Ilyes Choubani   Implementation Of...
189

1fa79b40   Jean-Philippe Bernard   added back passin...
190
;stop
452c334e   Ilyes Choubani   Implementation Of...
191

759a527d   Ilyes Choubani   general update
192
;PLOTTING OF THE PLUGIN(S)--------------- AUTOMATE THIS. QUITE FEASIBLE
452c334e   Ilyes Choubani   Implementation Of...
193
IF tag_exist(*!dustem_scope,'CONTINUUM') THEN BEGIN
759a527d   Ilyes Choubani   general update
194
  cgoplot,st.sed.wav,(*(*!dustem_plugin).continuum)[*,0],color='Teal',linestyle=3
427f1205   Jean-Michel Glorian   version 4.2 merged
195
ENDIF
4750086c   Ilyes Choubani   nouvelle philosph...
196
IF tag_exist(*!dustem_scope,'FREEFREE') THEN BEGIN
4fd64cbb   Ilyes Choubani   dustem_fit_sed_po...
197
  cgoplot,st.sed.wav,(*(*!dustem_plugin).freefree)[*,0],color='Dark Red',linestyle=3
b5ccb706   Jean-Philippe Bernard   improved to fit p...
198
ENDIF
452c334e   Ilyes Choubani   Implementation Of...
199
IF tag_exist(*!dustem_scope,'SYNCHROTRON') THEN BEGIN
4fd64cbb   Ilyes Choubani   dustem_fit_sed_po...
200
  cgoplot,st.sed.wav,(*(*!dustem_plugin).synchrotron)[*,0],color='Crimson',linestyle=3
b5ccb706   Jean-Philippe Bernard   improved to fit p...
201
ENDIF
452c334e   Ilyes Choubani   Implementation Of...
202

759a527d   Ilyes Choubani   general update
203
204
205
206
IF tag_exist(*!dustem_scope,'MBBDY_ISRF') THEN BEGIN
  cgoplot,st.sed.wav,(*(*!dustem_plugin).mbbdy_isrf)[*,0],color='Gold',linestyle=3
ENDIF

af6214c9   Ilyes Choubani   Added Modified-Bl...
207
IF tag_exist(*!dustem_scope,'MBBDY') THEN BEGIN
759a527d   Ilyes Choubani   general update
208
  cgoplot,st.sed.wav,(*(*!dustem_plugin).mbbdy)[*,0],color='Cornflower',linestyle=3
af6214c9   Ilyes Choubani   Added Modified-Bl...
209
210
211
ENDIF


9ccf7615   Jean-Philippe Bernard   modified to fit u...
212
cgoplot,st.sed.wav,spec/norm,color=use_col_tot,linestyle=use_line_tot
452c334e   Ilyes Choubani   Implementation Of...
213
214
;plot the normalized data as well. 
;----------------------------------------
427f1205   Jean-Michel Glorian   version 4.2 merged
215

9ccf7615   Jean-Philippe Bernard   modified to fit u...
216
;==== print the legend
759a527d   Ilyes Choubani   general update
217
frmt0='(A36)'
427f1205   Jean-Michel Glorian   version 4.2 merged
218
219
frmt1='(1E10.2)'
frmt2='(F7.2)'
4750086c   Ilyes Choubani   nouvelle philosph...
220
221
use_legend_xpos=0.50
use_legend_ypos=0.84
9be94157   Jean-Philippe Bernard   improved
222
use_legend_offset=0.03             ;This is the offset between lines of the legend in normalized units
4750086c   Ilyes Choubani   nouvelle philosph...
223
224
225
legend_charsize=0.86

k=0.
759a527d   Ilyes Choubani   general update
226
227
228
229
iscond=0
n_plgns = n_tags(*!dustem_scope)
inn=n_plgns/2+1
IF n_plgns mod 2 ne 0 THEN inn=n_plgns/2+2
4750086c   Ilyes Choubani   nouvelle philosph...
230

b5ccb706   Jean-Philippe Bernard   improved to fit p...
231
232
IF keyword_set(legend_xpos) THEN use_legend_xpos=legend_xpos
IF keyword_set(legend_ypos) THEN use_legend_ypos=legend_ypos
9be94157   Jean-Philippe Bernard   improved
233
IF keyword_set(legend_offset) THEN use_legend_offset=legend_offset
b5ccb706   Jean-Philippe Bernard   improved to fit p...
234

1a808a22   Jean-Philippe Bernard   improved
235
IF !d.name NE 'PS' THEN cleanplot
9ee42e40   Ilyes Choubani   fixed small bugs
236
;oo=0
759a527d   Ilyes Choubani   general update
237
238
tg=0
prv_str=''
427f1205   Jean-Michel Glorian   version 4.2 merged
239
IF keyword_set(res) THEN BEGIN
427f1205   Jean-Michel Glorian   version 4.2 merged
240
  Npar=n_elements(res)
7609fcde   Jean-Philippe Bernard   improved on crazy...
241
  ;print,'=============='
759a527d   Ilyes Choubani   general update
242
  
427f1205   Jean-Michel Glorian   version 4.2 merged
243
  FOR i=0L,Npar-1 DO BEGIN
7609fcde   Jean-Philippe Bernard   improved on crazy...
244
245
    parameter_description=(*(*!dustem_fit).param_descs)[i]
    parameter_type=dustem_parameter_description2type(parameter_description,string_name=string_name)
4750086c   Ilyes Choubani   nouvelle philosph...
246
    str=string(string_name+' = ',format=frmt0)+string(res[i],format=frmt1)
7609fcde   Jean-Philippe Bernard   improved on crazy...
247
    IF keyword_set(errors) THEN BEGIN
4750086c   Ilyes Choubani   nouvelle philosph...
248
      str=str+textoidl(' \pm ')+string(errors(i),format=frmt1)
9be94157   Jean-Philippe Bernard   improved
249
    ENDIF
452c334e   Ilyes Choubani   Implementation Of...
250
   
4750086c   Ilyes Choubani   nouvelle philosph...
251
252
253
    xxpos=use_legend_xpos*0.07
    yypos=use_legend_ypos*0.03
    xyouts,xxpos,yypos,'Model: '+!dustem_model,color=0,/normal,charsize=legend_charsize
dc72d0b6   Ilyes Choubani   initial procedure...
254
255
256
257
258
259
   
    IF STRUPCASE(strmid(strtrim(parameter_description,2),0,6)) eq 'DUSTEM' THEN BEGIN
       
;     xxpos=use_legend_xpos*0.07
;     yypos=use_legend_ypos*0.03
;     xyouts,xxpos,yypos,'Model: '+!dustem_model,color=0,/normal,charsize=legend_charsize
759a527d   Ilyes Choubani   general update
260
261
     
    xxpos=use_legend_xpos*0.75
4750086c   Ilyes Choubani   nouvelle philosph...
262
263
    yypos=use_legend_ypos*1.03
    xyouts,xxpos,yypos,'--Plugins--',color=0,/normal,charsize=legend_charsize
759a527d   Ilyes Choubani   general update
264
    
4750086c   Ilyes Choubani   nouvelle philosph...
265
    ii = strsplit(string_name,'_',count=countx) & ii = ii(countx-1)-1 ; Locating the last underscore to automate the extraction of the plugin's keyword
4750086c   Ilyes Choubani   nouvelle philosph...
266
    
759a527d   Ilyes Choubani   general update
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
    mm=where(tag_names(*!dustem_scope) eq strupcase(strmid(string_name,7,ii-7)),coun) ; Selecting a plugin through matching the string name of the plugin form the scope system variable with the one read from the parameter description vector
 
    ;tg+=1
    ;if strmid(string_name,7,ii-7) eq prv_str then tg-=1
    prmtg=(*(*!dustem_paramtag).(mm))
    indtg=(strmid(string_name,ii+1)) & indtg=strmid(indtg,0,/reverse_offset)   
    ;stop
    indtg=fix(indtg)
    prmtg=prmtg[indtg-1] 
    
    str=string(strmid(string_name,7,ii-7)+' ['+strmid(string_name,ii+1)+']: '+prmtg+' = ',format=frmt0)+string(res[i],format=frmt1)
   
    prv_str=strmid(string_name,7,ii-7)
    
    
    
4750086c   Ilyes Choubani   nouvelle philosph...
283
284
285
     IF keyword_set(errors) THEN BEGIN
       str=str+textoidl(' \pm ')+string(errors(i),format=frmt1)
     ENDIF
759a527d   Ilyes Choubani   general update
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
    
    xxpos=use_legend_xpos*0.46
    
    IF n_plgns gt 3 THEN BEGIN ;adapt the display of the plugins if there are more than three (display two columns)
        IF i eq inn+k THEN BEGIN
           k+=inn     
           ;iscond=1
           inn+=1
           xxpos=use_legend_xpos*0.06
        ENDIF
    ENDIF
              
;     IF iscond THEN BEGIN
;     inn+=1
;     xxpos=use_legend_xpos*0.06
;     ENDIF

    yypos=use_legend_ypos-(i-k)*use_legend_offset
4750086c   Ilyes Choubani   nouvelle philosph...
304
    xyouts,xxpos,yypos,str,color=0,/normal,charsize=legend_charsize
452c334e   Ilyes Choubani   Implementation Of...
305
    endif else begin
9ee42e40   Ilyes Choubani   fixed small bugs
306
307
308
309
310
311
    IF STRUPCASE(strmid(strtrim(parameter_description,2),0,24)) eq '(*!DUSTEM_PARAMS).GRAINS' and STRUPCASE(strmid(strtrim(parameter_description,2),3,1,/reverse_offset)) EQ 'O' then begin
     indpop=fix(STRUPCASE(strmid(strtrim(parameter_description,2),12,1,/reverse_offset)))
     ;oo+=1
     ;string_name=(((*!dustem_params).GRAINS).grain_type)[oo-1]
     string_name=(((*!dustem_params).GRAINS).grain_type)[indpop]
     ;stop
759a527d   Ilyes Choubani   general update
312
    endif
4750086c   Ilyes Choubani   nouvelle philosph...
313
314
315
316
317
    k+=1
    xxpos=use_legend_xpos*1.5
    yypos=use_legend_ypos*1.03
    xyouts,xxpos,yypos,'--Parameters--',color=0,/normal,charsize=legend_charsize
    yypos=use_legend_ypos-(i)*use_legend_offset 
759a527d   Ilyes Choubani   general update
318
319
    xxpos=use_legend_xpos*1.14
    str=string(string_name+' = ',format=frmt0)+string(res[i],format=frmt1)
4750086c   Ilyes Choubani   nouvelle philosph...
320
    xyouts,xxpos,yypos,str,color=0,/normal,charsize=legend_charsize    
452c334e   Ilyes Choubani   Implementation Of...
321
    endelse
427f1205   Jean-Michel Glorian   version 4.2 merged
322
  ENDFOR
7609fcde   Jean-Philippe Bernard   improved on crazy...
323
  ;stop
427f1205   Jean-Michel Glorian   version 4.2 merged
324
325
ENDIF
IF keyword_set(chi2) THEN BEGIN
759a527d   Ilyes Choubani   general update
326
  xxpos=1.29*use_legend_xpos
4750086c   Ilyes Choubani   nouvelle philosph...
327
  yypos=1.13*use_legend_ypos
452c334e   Ilyes Choubani   Implementation Of...
328
  xyouts,xxpos,yypos,string('chi2=',format=frmt0)+string(chi2,format=frmt2),color=0,/normal,charsize=legend_charsize
427f1205   Jean-Michel Glorian   version 4.2 merged
329
330
ENDIF
IF keyword_set(rchi2) THEN BEGIN
759a527d   Ilyes Choubani   general update
331
  xxpos=1.29*use_legend_xpos
4750086c   Ilyes Choubani   nouvelle philosph...
332
  yypos=1.13*use_legend_ypos-use_legend_offset
452c334e   Ilyes Choubani   Implementation Of...
333
  xyouts,xxpos,yypos,string('red. chi2=',format=frmt0)+string(rchi2,format=frmt2),color=0,/normal,charsize=legend_charsize
427f1205   Jean-Michel Glorian   version 4.2 merged
334
335
ENDIF

452c334e   Ilyes Choubani   Implementation Of...
336
xtit=textoidl('\lambda (\mum)')
8a88c1a3   Jean-Philippe Bernard   can't remember wh...
337
338
339
;cgplot,(*!dustem_data.sed).wav,(*!dustem_data.sed).values/sed,/nodata,xtit=xtit,ytit='Normalized',tit='',/xlog,xr=xr,/ys,/xs,yr=[0,2],ylog=0,position=[0.12,0.14,0.96,0.35],/noerase,yticks=2,ymino=2,xticklen=0.1
;stop
IF keyword_set(_extra) THEN BEGIN
759a527d   Ilyes Choubani   general update
340
  extra_kept={XR:[0.,0.]}
8a88c1a3   Jean-Philippe Bernard   can't remember wh...
341
  extra_tags=tag_names(_extra)
759a527d   Ilyes Choubani   general update
342
343
  ind=where(extra_tags EQ 'XR',count)
  IF count NE 0 THEN extra_kept.XR=_extra.(ind[0]) ;ELSE extra_kept=0
8a88c1a3   Jean-Philippe Bernard   can't remember wh...
344
ENDIF
759a527d   Ilyes Choubani   general update
345
cgplot,(*!dustem_data.sed).wav,(*!dustem_data.sed).values/sed,_extra=extra_kept,/nodata,xtit=xtit,ytit='Normalized',tit='',/xlog,/ys,/xs,yr=[0,2],ylog=0,position=[0.12,0.14,0.96,0.35],/noerase,yticks=2,ymino=2,xticklen=0.1,ytickformat='(F6.2)',charsize=1.3
452c334e   Ilyes Choubani   Implementation Of...
346
;plot the normalized data as well. 
7f2710c1   Jean-Philippe Bernard   modified to match...
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
IF count_spec NE 0 THEN BEGIN
  xx=((*!dustem_data.sed).wav)[ind_spec]
  yy=((*!dustem_data.sed).values/sed)[ind_spec]
  cgoplot,xx,yy,psym=16,symsize=1,thick=2,color=use_col_sed_spec
  trois_sigma=(3.*((*!dustem_data.sed).sigma)/2./sed)[ind_spec]
  cgerrplot,xx,yy-trois_sigma,yy+trois_sigma,color=use_col_sed_spec
ENDIF
IF count_filt NE 0 THEN BEGIN
  xx=((*!dustem_data.sed).wav)[ind_filt]
  yy=((*!dustem_data.sed).values/sed)[ind_filt]
  cgoplot,xx,yy,psym=16,symsize=1,thick=2,color='Dodger Blue'
  trois_sigma=(3.*((*!dustem_data.sed).sigma)/2./sed)[ind_filt]
  cgerrplot,xx,yy-trois_sigma,yy+trois_sigma,color='Dodger Blue'
ENDIF
;stop
;cgoplot,(*!dustem_data.sed).wav,(*!dustem_data.sed).values/sed,psym=16,symsize=1,thick=2,color='Dodger Blue'
cgoplot,10^!x.crange,replicate(1.,2),color='black',linestyle=0
;cgoplot,st.sed.wav,spec/spec,color='black'
;cgerrplot,((*!dustem_data.sed).wav),((*!dustem_data.sed).values)/sed-3.*((*!dustem_data.sed).sigma)/2./sed,((*!dustem_data.sed).values)/sed+3.*((*!dustem_data.sed).sigma)/2./sed,color='Dodger Blue'
452c334e   Ilyes Choubani   Implementation Of...
366
367
368



9ccf7615   Jean-Philippe Bernard   modified to fit u...
369
370
371
372
373
374
IF keyword_set(ps) THEN BEGIN
  device,/close
  set_plot,'X'
ENDIF

;stop
427f1205   Jean-Michel Glorian   version 4.2 merged
375
376
377
378

the_end:

END