Blame view

src/idl/dustem_plot_fit_sed.pro 16.3 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
                         help=help,win=win,ps=ps, $
266ae799   Ilyes Choubani   General update
5
                         legend_xpos=legend_xpos,legend_ypos=legend_ypos,legend_offset=legend_offset,fpol=fpol, $
452c334e   Ilyes Choubani   Implementation Of...
6
                         _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
  set_plot,'X'
266ae799   Ilyes Choubani   General update
62
    IF keyword_set(win) then window,win;,xsize=600,ysize=800
452c334e   Ilyes Choubani   Implementation Of...
63
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
9ccf7615   Jean-Philippe Bernard   modified to fit u...
66
67
68
;use_col_data_filt=70
;use_col_sed_spec=170
use_col_data_filt='blue'
9be94157   Jean-Philippe Bernard   improved
69
70
;use_col_sed_spec='red'
use_col_sed_spec='grey'
427f1205   Jean-Michel Glorian   version 4.2 merged
71
IF not keyword_set(col_sed) THEN BEGIN
9ccf7615   Jean-Philippe Bernard   modified to fit u...
72
73
  ;use_col_sed_filt=250     ;red
  use_col_sed_filt='red'     ;red
427f1205   Jean-Michel Glorian   version 4.2 merged
74
75
76
77
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...
78
79
  ;use_col_tot=200
  use_col_tot='black'
427f1205   Jean-Michel Glorian   version 4.2 merged
80
81
82
83
84
85
86
87
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
88

452c334e   Ilyes Choubani   Implementation Of...
89

427f1205   Jean-Michel Glorian   version 4.2 merged
90
spec = st.sed.em_tot * fact
266ae799   Ilyes Choubani   General update
91
if keyword_set(fpol) then specpol = st.polsed.em_tot * fact
452c334e   Ilyes Choubani   Implementation Of...
92
93
;ADDING PLUGIN(S) TO SPECTRUM----------------
;if n_tags(!dustem_data.sed) gt 1 then begin 
79991f38   Jean-Philippe Bernard   fixed for whan sc...
94
95
scopes=tag_names((*!dustem_scope))
IF scopes[0] NE 'NONE' THEN BEGIN
759a527d   Ilyes Choubani   general update
96
;IF ptr_valid(!dustem_plugin) THEN BEGIN
79991f38   Jean-Philippe Bernard   fixed for whan sc...
97
98
  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]
266ae799   Ilyes Choubani   General update
99
100
101
102
103
104
105
106
    if keyword_set(fpol) then begin
        IF total(strsplit((*(*!dustem_scope).(i)),'+',/extract) EQ 'REPLACE_QSED') THEN specpol=sqrt(((*(*!dustem_plugin).(i))[*,1])^2+((*(*!dustem_plugin).(i))[*,2])^2)
    endif
  ENDFOR
  FOR i=0L,n_tags(*!dustem_scope)-1 DO BEGIN
    if keyword_set(fpol) then begin    
        IF total(strsplit((*(*!dustem_scope).(i)),'+',/extract) EQ 'ADD_QSED') THEN specpol+=sqrt(((*(*!dustem_plugin).(i))[*,1])^2+((*(*!dustem_plugin).(i))[*,2])^2)
    endif  
79991f38   Jean-Philippe Bernard   fixed for whan sc...
107
108
  ENDFOR
ENDIF
452c334e   Ilyes Choubani   Implementation Of...
109
110
;endif
;------------------------------------------
427f1205   Jean-Michel Glorian   version 4.2 merged
111

6730c3f8   Jean-Philippe Bernard   modified to be co...
112
113
;stop

427f1205   Jean-Michel Glorian   version 4.2 merged
114
115
;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...
116
;col_off=30
6730c3f8   Jean-Philippe Bernard   modified to be co...
117
118
;Ngrains=(*!dustem_params).grain.Ngrains
Ngrains=(*!dustem_params).Ngrains
9ccf7615   Jean-Philippe Bernard   modified to fit u...
119
120
;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...
121
122
123
124
use_lines=replicate(0,Ngrains)

norm = sed * 0. + 1

389a2b1d   Jean-Philippe Bernard   improved
125
;====== PLOT THE SED
4750086c   Ilyes Choubani   nouvelle philosph...
126
127
128

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

759a527d   Ilyes Choubani   general update
129
130
131
132
133
134
135
136
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)')

266ae799   Ilyes Choubani   General update
137

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

266ae799   Ilyes Choubani   General update
140
141
142
;###############################
if keyword_set(fpol) then begin
    if !run_lin then begin
1f4818fe   Jean-Philippe Bernard   modified to work ...
143
144
      IF !d.name NE 'PS' THEN cgDisplay, 600, 500
      cgplot,(*!dustem_data.sed).wav,(*!dustem_data.sed).values/norm,/nodata,xtit='',ytit=ytit,tit='',/ylog,/xlog,/ys,/xs,position=[0.12,0.25,0.96,0.76],xtickformat='(A1)',_extra=_extra,charsize=1.3,/noerase    
266ae799   Ilyes Choubani   General update
145
146
147
148
149
    endif
endif ELSE 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
;###############################


1fa79b40   Jean-Philippe Bernard   added back passin...
150
;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)'
452c334e   Ilyes Choubani   Implementation Of...
151
152


266ae799   Ilyes Choubani   General update
153
;stop
452c334e   Ilyes Choubani   Implementation Of...
154
155
156
157
158
;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
159
160
161
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
2ca3af6c   Annie Hughes   fawlty psym bug
162
163
164
; following lines for fawlty compatibility
defsysv,'!psym',exists=pexist
if pexist eq 0 then defsysv,'!psym',0
427f1205   Jean-Michel Glorian   version 4.2 merged
165
166
IF count_spec NE 0 THEN BEGIN
  plotsym,0,/fill
9ccf7615   Jean-Philippe Bernard   modified to fit u...
167
168
169
  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...
170
  cgoplot,xx,yy,psym=8,syms=0.5,color=use_col_sed_spec
427f1205   Jean-Michel Glorian   version 4.2 merged
171
  IF not keyword_set(no_spec_error) THEN BEGIN
9be94157   Jean-Philippe Bernard   improved
172
    cgerrplot,xx,yy-rms,yy+rms,color=use_col_sed_spec
9ccf7615   Jean-Philippe Bernard   modified to fit u...
173
    ;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
174
175
176
  ENDIF
ENDIF
IF count_filt NE 0 THEN BEGIN
b5ccb706   Jean-Philippe Bernard   improved to fit p...
177
  ;stop
9ccf7615   Jean-Philippe Bernard   modified to fit u...
178
179
180
  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
181
  plotsym,0,/fill
452c334e   Ilyes Choubani   Implementation Of...
182
  cgoplot,xx,yy,psym=8,color='Dodger Blue';use_col_data_filt
9ccf7615   Jean-Philippe Bernard   modified to fit u...
183
  ;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...
184
  cgerrplot,xx,yy-rms,yy+rms,color='Dodger Blue';use_col_data_filt
427f1205   Jean-Michel Glorian   version 4.2 merged
185
186
187
188
ENDIF
;=== Plot the computed SED
IF count_filt NE 0 THEN BEGIN
  plotsym,8
9ccf7615   Jean-Philippe Bernard   modified to fit u...
189
190
  xx=((*!dustem_data.sed).wav)[ind_filt]
  yy=sed[ind_filt]/norm[ind_filt]
dc72d0b6   Ilyes Choubani   initial procedure...
191
  cgoplot,xx,yy,color=use_col_sed_filt,psym=6,syms=2
427f1205   Jean-Michel Glorian   version 4.2 merged
192
193
194
ENDIF
IF count_spec NE 0 THEN BEGIN
  plotsym,0
9ccf7615   Jean-Philippe Bernard   modified to fit u...
195
196
  xx=((*!dustem_data.sed).wav)[ind_spec]
  yy=sed[ind_spec]/norm[ind_spec]
dc72d0b6   Ilyes Choubani   initial procedure...
197
  cgoplot,xx,yy,color=use_col_sed_filt,psym=6,syms=2
427f1205   Jean-Michel Glorian   version 4.2 merged
198
199
200
ENDIF


9ccf7615   Jean-Philippe Bernard   modified to fit u...
201
IF !dustem_show_plot EQ 2 THEN BEGIN
427f1205   Jean-Michel Glorian   version 4.2 merged
202
	norm = spec
9ccf7615   Jean-Philippe Bernard   modified to fit u...
203
ENDIF ELSE BEGIN
427f1205   Jean-Michel Glorian   version 4.2 merged
204
	norm = spec * 0. + 1
9ccf7615   Jean-Philippe Bernard   modified to fit u...
205
ENDELSE
266ae799   Ilyes Choubani   General update
206
use_cols[1]='Cornflower'
427f1205   Jean-Michel Glorian   version 4.2 merged
207
FOR i=0L,Ngrains-1 DO BEGIN
9ccf7615   Jean-Philippe Bernard   modified to fit u...
208
  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
209
ENDFOR
452c334e   Ilyes Choubani   Implementation Of...
210

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

759a527d   Ilyes Choubani   general update
213
;PLOTTING OF THE PLUGIN(S)--------------- AUTOMATE THIS. QUITE FEASIBLE
452c334e   Ilyes Choubani   Implementation Of...
214
IF tag_exist(*!dustem_scope,'CONTINUUM') THEN BEGIN
759a527d   Ilyes Choubani   general update
215
  cgoplot,st.sed.wav,(*(*!dustem_plugin).continuum)[*,0],color='Teal',linestyle=3
427f1205   Jean-Michel Glorian   version 4.2 merged
216
ENDIF
4750086c   Ilyes Choubani   nouvelle philosph...
217
IF tag_exist(*!dustem_scope,'FREEFREE') THEN BEGIN
4fd64cbb   Ilyes Choubani   dustem_fit_sed_po...
218
  cgoplot,st.sed.wav,(*(*!dustem_plugin).freefree)[*,0],color='Dark Red',linestyle=3
b5ccb706   Jean-Philippe Bernard   improved to fit p...
219
ENDIF
452c334e   Ilyes Choubani   Implementation Of...
220
IF tag_exist(*!dustem_scope,'SYNCHROTRON') THEN BEGIN
4fd64cbb   Ilyes Choubani   dustem_fit_sed_po...
221
  cgoplot,st.sed.wav,(*(*!dustem_plugin).synchrotron)[*,0],color='Crimson',linestyle=3
b5ccb706   Jean-Philippe Bernard   improved to fit p...
222
ENDIF
452c334e   Ilyes Choubani   Implementation Of...
223

759a527d   Ilyes Choubani   general update
224
225
226
227
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...
228
IF tag_exist(*!dustem_scope,'MBBDY') THEN BEGIN
759a527d   Ilyes Choubani   general update
229
  cgoplot,st.sed.wav,(*(*!dustem_plugin).mbbdy)[*,0],color='Cornflower',linestyle=3
af6214c9   Ilyes Choubani   Added Modified-Bl...
230
231
232
ENDIF


9ccf7615   Jean-Philippe Bernard   modified to fit u...
233
cgoplot,st.sed.wav,spec/norm,color=use_col_tot,linestyle=use_line_tot
266ae799   Ilyes Choubani   General update
234
if keyword_set(fpol) then cgoplot,st.polsed.wav,specpol,color='Teal',linestyle=4
452c334e   Ilyes Choubani   Implementation Of...
235
236
;plot the normalized data as well. 
;----------------------------------------
427f1205   Jean-Michel Glorian   version 4.2 merged
237

9ccf7615   Jean-Philippe Bernard   modified to fit u...
238
;==== print the legend
759a527d   Ilyes Choubani   general update
239
frmt0='(A36)'
427f1205   Jean-Michel Glorian   version 4.2 merged
240
241
frmt1='(1E10.2)'
frmt2='(F7.2)'
4750086c   Ilyes Choubani   nouvelle philosph...
242
use_legend_xpos=0.50
266ae799   Ilyes Choubani   General update
243
if keyword_set(fpol) then use_legend_ypos=0.70 ELSE use_legend_ypos=0.84
9be94157   Jean-Philippe Bernard   improved
244
use_legend_offset=0.03             ;This is the offset between lines of the legend in normalized units
4750086c   Ilyes Choubani   nouvelle philosph...
245
246
247
legend_charsize=0.86

k=0.
759a527d   Ilyes Choubani   general update
248
249
250
251
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...
252

b5ccb706   Jean-Philippe Bernard   improved to fit p...
253
254
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
255
IF keyword_set(legend_offset) THEN use_legend_offset=legend_offset
b5ccb706   Jean-Philippe Bernard   improved to fit p...
256

1a808a22   Jean-Philippe Bernard   improved
257
IF !d.name NE 'PS' THEN cleanplot
266ae799   Ilyes Choubani   General update
258

759a527d   Ilyes Choubani   general update
259
260
tg=0
prv_str=''
427f1205   Jean-Michel Glorian   version 4.2 merged
261
IF keyword_set(res) THEN BEGIN
427f1205   Jean-Michel Glorian   version 4.2 merged
262
  Npar=n_elements(res)
7609fcde   Jean-Philippe Bernard   improved on crazy...
263
  ;print,'=============='
759a527d   Ilyes Choubani   general update
264
  
427f1205   Jean-Michel Glorian   version 4.2 merged
265
  FOR i=0L,Npar-1 DO BEGIN
7609fcde   Jean-Philippe Bernard   improved on crazy...
266
267
    parameter_description=(*(*!dustem_fit).param_descs)[i]
    parameter_type=dustem_parameter_description2type(parameter_description,string_name=string_name)
4750086c   Ilyes Choubani   nouvelle philosph...
268
    str=string(string_name+' = ',format=frmt0)+string(res[i],format=frmt1)
7609fcde   Jean-Philippe Bernard   improved on crazy...
269
    IF keyword_set(errors) THEN BEGIN
4750086c   Ilyes Choubani   nouvelle philosph...
270
      str=str+textoidl(' \pm ')+string(errors(i),format=frmt1)
9be94157   Jean-Philippe Bernard   improved
271
    ENDIF
452c334e   Ilyes Choubani   Implementation Of...
272
   
4750086c   Ilyes Choubani   nouvelle philosph...
273
274
275
    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...
276
277
278
279
280
281
   
    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
282
283
     
    xxpos=use_legend_xpos*0.75
4750086c   Ilyes Choubani   nouvelle philosph...
284
285
    yypos=use_legend_ypos*1.03
    xyouts,xxpos,yypos,'--Plugins--',color=0,/normal,charsize=legend_charsize
759a527d   Ilyes Choubani   general update
286
    
4750086c   Ilyes Choubani   nouvelle philosph...
287
    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...
288
    
759a527d   Ilyes Choubani   general update
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
    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...
305
306
307
     IF keyword_set(errors) THEN BEGIN
       str=str+textoidl(' \pm ')+string(errors(i),format=frmt1)
     ENDIF
759a527d   Ilyes Choubani   general update
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
    
    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...
326
    xyouts,xxpos,yypos,str,color=0,/normal,charsize=legend_charsize
452c334e   Ilyes Choubani   Implementation Of...
327
    endif else begin
9ee42e40   Ilyes Choubani   fixed small bugs
328
329
330
331
332
333
    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
334
    endif
4750086c   Ilyes Choubani   nouvelle philosph...
335
336
337
338
339
    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
340
341
    xxpos=use_legend_xpos*1.14
    str=string(string_name+' = ',format=frmt0)+string(res[i],format=frmt1)
4750086c   Ilyes Choubani   nouvelle philosph...
342
    xyouts,xxpos,yypos,str,color=0,/normal,charsize=legend_charsize    
452c334e   Ilyes Choubani   Implementation Of...
343
    endelse
427f1205   Jean-Michel Glorian   version 4.2 merged
344
  ENDFOR
7609fcde   Jean-Philippe Bernard   improved on crazy...
345
  ;stop
427f1205   Jean-Michel Glorian   version 4.2 merged
346
347
ENDIF
IF keyword_set(chi2) THEN BEGIN
759a527d   Ilyes Choubani   general update
348
  xxpos=1.29*use_legend_xpos
266ae799   Ilyes Choubani   General update
349
  yypos=1.13*0.84;use_legend_ypos
452c334e   Ilyes Choubani   Implementation Of...
350
  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
351
352
ENDIF
IF keyword_set(rchi2) THEN BEGIN
759a527d   Ilyes Choubani   general update
353
  xxpos=1.29*use_legend_xpos
266ae799   Ilyes Choubani   General update
354
  yypos=1.13*0.84-use_legend_offset;use_legend_ypos-use_legend_offset
452c334e   Ilyes Choubani   Implementation Of...
355
  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
356
357
ENDIF

452c334e   Ilyes Choubani   Implementation Of...
358
xtit=textoidl('\lambda (\mum)')
8a88c1a3   Jean-Philippe Bernard   can't remember wh...
359
360
;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
266ae799   Ilyes Choubani   General update
361

8a88c1a3   Jean-Philippe Bernard   can't remember wh...
362
IF keyword_set(_extra) THEN BEGIN
759a527d   Ilyes Choubani   general update
363
  extra_kept={XR:[0.,0.]}
8a88c1a3   Jean-Philippe Bernard   can't remember wh...
364
  extra_tags=tag_names(_extra)
759a527d   Ilyes Choubani   general update
365
366
  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...
367
ENDIF
266ae799   Ilyes Choubani   General update
368
369
370
371
372
373

;stop
;,position=[0.12,0.14,0.96,0.35] old position before your polfrac display modification
if keyword_set(fpol) then begin
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.1,0.96,0.25],/noerase,yticks=2,ymino=2,xticklen=0.1,ytickformat='(F6.2)',charsize=1.3
endif else 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...
374
;plot the normalized data as well. 
7f2710c1   Jean-Philippe Bernard   modified to match...
375
376
377
378
379
380
381
382
383
384
385
386
387
388
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
266ae799   Ilyes Choubani   General update
389

7f2710c1   Jean-Philippe Bernard   modified to match...
390
391
392
393
394
;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...
395
396


266ae799   Ilyes Choubani   General update
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
if keyword_set(fpol) then begin
    plotsym,0,/fill
    cgplot, (*!dustem_data.polfrac).wav,(*!dustem_data.polfrac).values*100,/nodata,xtit='',tit=title,ytit='',/xlog,/ylog,/ys,/xs,position=[0.12,0.76,0.96,0.91],charsize=1.3,yr=[1.0E-1,30.0],/noerase,xticklen=0.1,xtickformat='(A1)',_extra=extra_kept;,xr=_extra.xr
    xxpos=use_legend_xpos*0.35
    yypos=use_legend_ypos*1.25
    xyouts,xxpos,yypos,'Polarization fraction (%)',color=cgcolor('purple'),charsize=legend_charsize,/normal
    yypos=use_legend_ypos*1.20
    stringg='Polarization SED '+'('+textoidl('P_{\nu}')+')'
    xyouts,xxpos,yypos,stringg,color=cgcolor('teal'),charsize=legend_charsize,/normal
    pilotfx=fpol(0);((*!dustem_data.polfrac).values)(0);fpol(0);
    cgoplot, (*!dustem_data.polfrac).wav,(*!dustem_data.polfrac).values*100,charsize=1.3,psym=8,syms=1,thick=2,color='Dodger Blue'   
    cgoplot, st.polsed.wav,(specpol/spec)*100/pilotfx*((*!dustem_data.polfrac).values)(0),color='purple'
    cgoplot, (*!dustem_data.polfrac).wav,fpol*100/pilotfx*((*!dustem_data.polfrac).values)(0),color='Red',psym=6,syms=1
    ;fpol=abs(fpol)
    ;delp=(*!dustem_data.polfrac).values*100-fpol*100/pilotfx*((*!dustem_data.polfrac).values)(0)
    ;cgoplot, ((*!dustem_data.polfrac).wav),((*!dustem_data.polfrac).values*100+delp),charsize=1.3,color='black',linestyle=2
    ;stop
endif
452c334e   Ilyes Choubani   Implementation Of...
415

9ccf7615   Jean-Philippe Bernard   modified to fit u...
416
417
418
419
420
421
IF keyword_set(ps) THEN BEGIN
  device,/close
  set_plot,'X'
ENDIF

;stop
427f1205   Jean-Michel Glorian   version 4.2 merged
422
423
424
425

the_end:

END