Blame view

src/idl/dustem_init.pro 17.5 KB
b7f936fc   Ilyes Choubani   to JP: initial fi...
1
PRO dustem_init,dir=dir,wraptest=wraptest,plot_it=plot_it,model=model,help=help,noerase=noerase,st_model=st_model,pol=pol,verbose=verbose,kwords=kwords
427f1205   Jean-Michel Glorian   version 4.2 merged
2
3
4
5
6
7
8
9
10

;+
; NAME:
;   dustem_init
; CALLING SEQUENCE:
;   dustem_init
; PURPOSE:
;   Defines system variables to run the DUSTEM code
; INPUTS:
e69bf245   Jean-Philippe Bernard   improved
11
;    model    = Selects one of the dust mixture used by dustem
427f1205   Jean-Michel Glorian   version 4.2 merged
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
49
;              'COMPIEGNE_ETAL2010' from Compiegne et al 2010 (default)
;              'DBP90' from Desert et al 1990
;              'DL01' from Draine & Li 2001
;              'DL07' from Draine & Li 2007
;   dir      = overrides default directory where to read data
;   wraptest = test running dustem f90 through the wrapper
;   plot_it  = plots run result (only if wraptest)
;   help     = If set print this help
; OPTIONAL INPUT:
;   None
; OUTPUTS:
;   None
; PROCEDURE AND SUBROUTINE USED
;    1/ The folowing system variables are initialized to null values
;	or empty pointers:
;       !dustem_fit
;       !dustem_data
;       !dustem_inputs
;       !dustem_params
;       !run_ionfrac
;       !dustem_idl_continuum
;       !dustem_filters
;       !dustem_verbose
;       !dustem_show_plot
;    2/ optionally runs the fortran code (if wraptest)
;       This step calls the Fortran code to run a standard model
;    3/ !dustem_filters is initialized calling dustem_filter_init.pro.
; RESTRICTIONS:
;    The dustem fortran code must be installed
;    The dustem idl wrapper must be installed
; EXAMPLES
;    dustem_init,/wrap,/plot_it
; MODIFICATION HISTORY:
;    See cvs logs
;    Written by JPB,NF,DP Jan-2007
;    see evolution details on the dustem cvs maintained at CESR
;-

6d4eaab4   Ilyes Choubani   Replacing !dustem...
50
51
52
53
54
55
56
57
;IC 
;I think this procedure should be throughly revised. (and also the rest of the code corrected)
;Pointers are used when the need does not present itself. 
;ie: defsysv, '!dustem_fit', ptr_new(dustem_fit_st), defsysv,'!dustem_inputs',ptr_new() or defsysv,'!dustem_params',ptr_new() which don't require initialization for instance




427f1205   Jean-Michel Glorian   version 4.2 merged
58
59
60
61
62
IF keyword_set(help) THEN BEGIN
  doc_library,'dustem_init'
  goto,the_end
ENDIF

d012e324   Ilyes Choubani   FIX to the use of...
63
dustem_define_la_common 
5a7a4415   Jean-Philippe Bernard   adapted to new fi...
64

0e608856   Jean-Philippe Bernard   improved
65
66
67
defsysv,'!dustem_verbose',0             ;1=verbose
IF keyword_set(verbose) THEN !dustem_verbose=1

b5ccb706   Jean-Philippe Bernard   improved to fit p...
68
69
70
defsysv,'!run_pol',0             ;0=no polar
IF keyword_set(pol) THEN !run_pol=1

427f1205   Jean-Michel Glorian   version 4.2 merged
71
72
73
74
75
;=== color correction system variables
defsysv,'!dustem_previous_cc',ptr_new()   ;store previous color correction values
defsysv,'!dustem_do_cc',1   ;indicates to dustem if color corrections are needed. Will be changed when fitting
defsysv,'!dustem_never_do_cc',0   ;set to 1 to never do color corrections (not recommanded, but faster).

66aff855   Jean-Philippe Bernard   modified to impro...
76
77
78
79
80
;This is for polarization
defsysv, '!run_circ', 0.  
defsysv, '!run_anis', 0.  
defsysv, '!run_rrf', 0.    
defsysv, '!run_univ', 0.    
389a2b1d   Jean-Philippe Bernard   improved
81
defsysv, '!run_lin', 0.
66aff855   Jean-Philippe Bernard   modified to impro...
82

62a2393e   Jean-Philippe Bernard   added redshift
83
84
defsysv, '!dustem_redshift', 0.    ;in case the SED needs to be shifted for a non zero redshift

83b3ddee   Jean-Philippe Bernard   modified with Ily...
85
86
;This is just to make sure that plugin system variables are created even if no plugins are used
pd_bidon=['NONE']
5f04fa07   Ilyes Choubani   general update
87

83b3ddee   Jean-Philippe Bernard   modified with Ily...
88
89
dustem_init_plugins,pd_bidon

bcbe1386   Jean-Philippe Bernard   introduced use of...
90
91
defsysv,'!dustem_nocatch',0   ;set to catch errors in sed fitting.

83b3ddee   Jean-Philippe Bernard   modified with Ily...
92
93
;stop

389a2b1d   Jean-Philippe Bernard   improved
94
;==== define a stellar modyfier to the ISRF
4750086c   Ilyes Choubani   nouvelle philosph...
95
96

;toto=dustem_define_isrf_stellar_modifyer_variable()
389a2b1d   Jean-Philippe Bernard   improved
97

427f1205   Jean-Michel Glorian   version 4.2 merged
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
file=!dustem_wrap_soft_dir+'instrument_description.xcat'
st=read_xcat(file,/silent)
defsysv,'!dustem_instrument_description',st

defsysv,'!indef', exists=exists_indef
IF NOT exists_indef THEN defsysv,'!indef',-32768.

;define !dustem_fit
dustem_fit_st={data:ptr_new(),wavelength:ptr_new(), $
               param_descs:ptr_new(),param_init_values:ptr_new(),param_func:ptr_new(), $
               fixed_param_descs:ptr_new(),fixed_param_init_values:ptr_new(), $
               chi2:0.D0,rchi2:0.D0, $
               current_param_values:ptr_new(), current_param_errors:ptr_new() $
               }
defsysv, '!dustem_fit', ptr_new(dustem_fit_st)    ;Data to fit

c8368c6e   Ilyes Choubani   updating plotting...
114
115
116



427f1205   Jean-Michel Glorian   version 4.2 merged
117
118
if keyword_set(pol) then begin
	defsysv, '!dustem_data', {    $ ;Data to fit
68598bce   Ilyes Choubani   reducing number o...
119
120
                                sed:    ptr_new(),      $ ; 
                                ext:    ptr_new(),      $ ;
68598bce   Ilyes Choubani   reducing number o...
121
122
                                qsed: ptr_new(),        $ ; 
                                used: ptr_new(),        $ ; 
5f04fa07   Ilyes Choubani   general update
123
124
125
                                polsed: ptr_new(),      $ ; 
                                polfrac: ptr_new(),     $ ;   
                                psi_em: ptr_new(),      $ ; 
68598bce   Ilyes Choubani   reducing number o...
126
                                qext: ptr_new(),        $ ; 
5f04fa07   Ilyes Choubani   general update
127
128
129
130
                                uext: ptr_new(),        $ ;
                                polext: ptr_new(),      $ ;  
                                psi_ext: ptr_new()      $ ; 
                                 
68598bce   Ilyes Choubani   reducing number o...
131
132
                         }
    
5f04fa07   Ilyes Choubani   general update
133
134
         
         rchi2_weight = {sed: 0.,ext: 0.,qsed:0.,used:0.,polsed:0.,polfrac:0.,psi_em:0.,qext:0.,uext:0.,polext:0.,psi_ext:0.}
68598bce   Ilyes Choubani   reducing number o...
135
136
         
    defsysv,'!dustem_show', {    $ ;Data to fit
5f04fa07   Ilyes Choubani   general update
137
138
139
140
141
142
143
144
145
146
147
148
                                sed:    ptr_new(),      $ ; 
                                ext:    ptr_new(),      $ ;
                                qsed: ptr_new(),        $ ; 
                                used: ptr_new(),        $ ; 
                                polsed: ptr_new(),      $ ; 
                                polfrac: ptr_new(),     $ ;   
                                psi_em: ptr_new(),      $ ; 
                                qext: ptr_new(),        $ ; 
                                uext: ptr_new(),        $ ;
                                polext: ptr_new(),      $ ;  
                                psi_ext: ptr_new()      $ ; 
                                 
68598bce   Ilyes Choubani   reducing number o...
149
150
                         }     
         
427f1205   Jean-Michel Glorian   version 4.2 merged
151
endif else begin
c8368c6e   Ilyes Choubani   updating plotting...
152
	
427f1205   Jean-Michel Glorian   version 4.2 merged
153
154
155
156
157
	defsysv, '!dustem_data', {    $ ;Data to fit
                                sed:    ptr_new(),      $
                                ext:    ptr_new()       $
                         }
	rchi2_weight = {sed: 0.,ext: 0.}
68598bce   Ilyes Choubani   reducing number o...
158
159
160
161
162
	
	defsysv, '!dustem_show', {    $ ;Data to fit
                                sed:    ptr_new(),      $
                                ext:    ptr_new()       $
                         }
427f1205   Jean-Michel Glorian   version 4.2 merged
163
164
endelse

68598bce   Ilyes Choubani   reducing number o...
165

c8368c6e   Ilyes Choubani   updating plotting...
166
167
168
169
170
171
172
if !run_pol then begin
    tagnames=tag_names(!dustem_data)
    testpol = tagnames EQ 'POLSED' or tagnames EQ 'POLEXT' or tagnames EQ 'POLFRAC' or tagnames EQ 'POLSED' or tagnames EQ 'PSI_EM' or tagnames EQ 'PSI_EXT'
    ind_data=where(~testpol,ctestpol)
    if ctestpol ne 0 then tagnames =(tag_names(!dustem_data))[ind_data] 

endif else tagnames=tag_names(!dustem_data)
68598bce   Ilyes Choubani   reducing number o...
173

427f1205   Jean-Michel Glorian   version 4.2 merged
174
175
176
177
178
179
180
181
instr="defsysv, '!fit_rchi2_weight', {"
FOR i = 0, n_elements(tagnames)-1 DO BEGIN
  instr+=tagnames(i)+': rchi2_weight.'+tagnames(i)
  IF i NE n_elements(tagnames)-1 THEN instr+=','
ENDFOR
instr+='}'
toto=execute(instr)

68598bce   Ilyes Choubani   reducing number o...
182
183
184
;#########system variables necessary for cgwindow plotting##########     
defsysv, '!dustemcgwin_id', {    $ ;IDs of windows to plot                  
                            sed:    la_undef(),      $                          
5f04fa07   Ilyes Choubani   general update
185
186
187
188
                            ext:    la_undef(),      $
                            prms:   la_undef(),      $
                            plgns:  la_undef()       $
                                             
68598bce   Ilyes Choubani   reducing number o...
189
                     }                                                      
5f04fa07   Ilyes Choubani   general update
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
; ;I am doing this to save time instead of filtering the _extra structure
; ;This part is not used so I will comment it
; defsysv, '!dustemcgwin_extra', {    $ ;Data to fit
;                             sed:    ptr_new(),      $ ; 
;                             ext:    ptr_new(),      $ ;
;                             qsed: ptr_new(),        $ ; 
;                             used: ptr_new(),        $ ; 
;                             polsed: ptr_new(),      $ ; 
;                             polfrac: ptr_new(),     $ ;   
;                             psi_em: ptr_new(),      $ ; 
;                             qext: ptr_new(),        $ ; 
;                             uext: ptr_new(),        $ ;
;                             polext: ptr_new(),      $ ;  
;                             psi_ext: ptr_new()      $ ; 
;                              
;                      }
18e4331f   Ilyes Choubani   general update (f...
206
207

  
68598bce   Ilyes Choubani   reducing number o...
208
                                                                                                
5f04fa07   Ilyes Choubani   general update
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
defsysv, '!dustemcgwin_ncmds', {    $ ;Data to fit
                            sed:     {pl:0, nrm:0},      $ ; 
                            ext:     {pl:0, nrm:0},      $ ;
                            qsed:    {pl:0, nrm:0},      $ ; 
                            used:    {pl:0, nrm:0},      $ ; 
                            polsed:  {pl:0, nrm:0},      $ ; 
                            polfrac: {pl:0},             $ ;   
                            psi_em:  {pl:0},             $ ; 
                            qext:    {pl:0, nrm:0},      $ ; 
                            uext:    {pl:0, nrm:0},      $ ;
                            polext:  {pl:0, nrm:0},      $ ;  
                            psi_ext: {pl:0},             $ ;
                            chi2 :   {pl:0, txtwdth:0.}, $ ; ;beacause chi2 needs to be updated (needing the command index)
                            rchi2 :  {pl:0, txtwdth:0.}, $ ;
                            pltit :  {pl:0, txtwdth:0.}, $ ; plot title
                            prms :   {pl:0},             $ ;
                            plgns :  {pl:0}             $ ;
                     }
                                                         

;Necessary for the modified logarithm plotting (negative values + positive values)                                                                                                
68598bce   Ilyes Choubani   reducing number o...
230
231
232
233
234
defsysv, '!dustem_mlog', 0  ;necessary for the plotting of negative values on the axis in dstmwrp_exp.pro                                                                 
;###################################################################


defsysv, '!dustem_psi', 0.
3ff9cac3   Ilyes Choubani   general update
235

86e5c5c1   Ilyes Choubani   General update + ...
236

6d4eaab4   Ilyes Choubani   Replacing !dustem...
237
                     
427f1205   Jean-Michel Glorian   version 4.2 merged
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
;IDL> help,*!dustem_data,/str
;** Structure <2173b20>, 4 tags, length=448, data length=448, refs=1:
;   INSTRU_NAMES    STRING    Array[14]
;   FILT_NAMES      STRING    Array[14]
;   VALUES          FLOAT     Array[14]
;   SIGMA           FLOAT     Array[14]
defsysv,'!dustem_inputs',ptr_new()    ;dustem input files

;=== This is not a system variable anymore
;defsysv, '!dustem_ext', ptr_new()    ;Contains the values of extinction
;=== This is not a system variable anymore
;defsysv, '!dustem_specem', ptr_new() ;Contains the values of emission

defsysv, '!dustem_params', ptr_new() ;Contains the values of all Desert Model parameters (except extinction !)
;IDL> help,*!dustem_params,/str
;** Structure <2926e10>, 7 tags, length=13312, data length=13282, refs=1:
;   GRAINS          STRUCT    -> <Anonymous> Array[3]
;   GEMISSIV        STRUCT    -> <Anonymous> Array[300]
;   ISRF            STRUCT    -> <Anonymous> Array[64]
;   QABS            STRUCT    -> <Anonymous> Array[64]
;   CALOR           STRUCT    -> <Anonymous> Array[5]
;   SPECEM          STRUCT    -> <Anonymous> Array[1]
;   IONFRAC         STRUCT    -> <Anonymous> Array[10]

;defsysv, '!dustem_fit_sed',ptr_new()          ;Best fit SED

;The following is not used in the WEB3p8 version of the code
;Only in the VERSTRAETE version of the code.
;IF getenv('DUSTEM_WHICH') EQ 'VERSTRAETE' THEN BEGIN
  defsysv, '!run_ionfrac', 0.     ; 0:no call to dustem_create_ionfrac UNLESS it is called as a param
                                  ; 1:call to dustem_create_ionfrac with the MIX_xxx.DAT files
                                  ; 2:call to dustem_create_ionfrac with the SIZE_xxx.DAT files
;ENDIF

427f1205   Jean-Michel Glorian   version 4.2 merged
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
defsysv,'!dustem_filters',ptr_new()     ;filter information (filled by dustem_filter_init.pro)
;; IDL> help,*!dustem_filters,/str
;; ** Structure <1b95608>, 17 tags, length=8232, data length=8118, refs=1:
;;    IRAC            STRUCT    -> <Anonymous> Array[1]
;;    MIPS            STRUCT    -> <Anonymous> Array[1]
;;    MSX             STRUCT    -> <Anonymous> Array[1]
;;    IRAS            STRUCT    -> <Anonymous> Array[1]
;;    DIRBE           STRUCT    -> <Anonymous> Array[1]
;;    SPM             STRUCT    -> <Anonymous> Array[1]
;;    ISOCAM          STRUCT    -> <Anonymous> Array[1]
;;    ISOPHOTP        STRUCT    -> <Anonymous> Array[1]
;;    ISOPHOTC        STRUCT    -> <Anonymous> Array[1]
;;    EFIRAS          STRUCT    -> <Anonymous> Array[1]
;;    ARCHEOPS        STRUCT    -> <Anonymous> Array[1]
;;    HFI             STRUCT    -> <Anonymous> Array[1]
;;    LFI             STRUCT    -> <Anonymous> Array[1]
;;    WMAP            STRUCT    -> <Anonymous> Array[1]
;;    SPIRE           STRUCT    -> <Anonymous> Array[1]
;;    PACS            STRUCT    -> <Anonymous> Array[1]
;;    AKARI           STRUCT    -> <Anonymous> Array[1]

4750086c   Ilyes Choubani   nouvelle philosph...
293
defsysv,'!dustem_verbose',0                                  ;1=verbose
427f1205   Jean-Michel Glorian   version 4.2 merged
294
295
defsysv,'!dustem_show_plot',1           ;0=show no plot

607060e5   Ilyes Choubani   test version
296

427f1205   Jean-Michel Glorian   version 4.2 merged
297
298
299
300
301
302
;apparently not needed anymore. Was removed.
;defsysv,'!ki',0.  ;apparently needed by mpfit, but what is it ?

;== This is for the default mode
dustem_inputs={GRAIN:'GRAIN.DAT',ISRF:'ISRF.DAT',ALIGN:'ALIGN.DAT'}
!dustem_inputs=ptr_new(dustem_inputs)
266ae799   Ilyes Choubani   General update
303
304


68598bce   Ilyes Choubani   reducing number o...
305
defsysv, '!dustem_HCD', ptr_new(1.00E20) ;I do not see the reason behind using a pointer in this case.
266ae799   Ilyes Choubani   General update
306
307


427f1205   Jean-Michel Glorian   version 4.2 merged
308
;===This is the Desert option
759a527d   Ilyes Choubani   general update
309

e69bf245   Jean-Philippe Bernard   improved
310
IF keyword_set(model) THEN BEGIN
4750086c   Ilyes Choubani   nouvelle philosph...
311
312
313

defsysv, '!dustem_model', model

759a527d   Ilyes Choubani   general update
314

e69bf245   Jean-Philippe Bernard   improved
315
  CASE model OF
427f1205   Jean-Michel Glorian   version 4.2 merged
316
317
318
319
320
321
322
323
324
325
326
    'COMPIEGNE_ETAL2010':BEGIN
      (*!dustem_inputs).grain='GRAIN_MC10.DAT'
    END
    'DBP90':BEGIN
      (*!dustem_inputs).grain='GRAIN_DBP90.DAT'
    END
    'DL01':BEGIN
      (*!dustem_inputs).grain='GRAIN_DL01.DAT'
    END
    'DL07':BEGIN
      (*!dustem_inputs).grain='GRAIN_DL07.DAT'
b5ccb706   Jean-Philippe Bernard   improved to fit p...
327
328
    END
    'AJ13':BEGIN
427f1205   Jean-Michel Glorian   version 4.2 merged
329
      (*!dustem_inputs).grain='GRAIN_J13.DAT'
b5ccb706   Jean-Philippe Bernard   improved to fit p...
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
    END
    'G17_MODELA':BEGIN
      (*!dustem_inputs).grain='GRAIN_G17_MODELA.DAT'
      (*!dustem_inputs).align='ALIGN_G17_MODELA.DAT'
    END
    'G17_MODELB':BEGIN
      (*!dustem_inputs).grain='GRAIN_G17_MODELB.DAT'
      (*!dustem_inputs).align='ALIGN_G17_MODELB.DAT'
    END
    'G17_MODELC':BEGIN
      (*!dustem_inputs).grain='GRAIN_G17_MODELC.DAT'
      (*!dustem_inputs).align='ALIGN_G17_MODELC.DAT'
    END
    'G17_MODELD':BEGIN
      (*!dustem_inputs).grain='GRAIN_G17_MODELD.DAT'
      (*!dustem_inputs).align='ALIGN_G17_MODELD.DAT'
    END
2399e73e   Jean-Philippe Bernard   imprved towards r...
347
348
    'THEMIS':BEGIN
      (*!dustem_inputs).grain='GRAIN_THEMIS.DAT'
d012e324   Ilyes Choubani   FIX to the use of...
349
      (*!dustem_inputs).align='ALIGN_THEMIS.DAT'
2399e73e   Jean-Philippe Bernard   imprved towards r...
350
    END
b0cabd3c   Ilyes Choubani   general update
351
352
353
    'NY_MODELA':BEGIN
      (*!dustem_inputs).grain='GRAIN_NY_MODELA.DAT'
      (*!dustem_inputs).align='ALIGN_G17_MODELA.DAT' 
266ae799   Ilyes Choubani   General update
354
    END
6d4eaab4   Ilyes Choubani   Replacing !dustem...
355
    ;This is a user-defined model ;This will prolly have to get modified.    
266ae799   Ilyes Choubani   General update
356
357
358
    'USER_MODEL':BEGIN
      (*!dustem_inputs).grain='GRAIN_USER.DAT' 
    END
427f1205   Jean-Michel Glorian   version 4.2 merged
359
    ELSE:BEGIN
26361fb3   Jean-Philippe Bernard   improved
360
      message,'model '+model+' unknown',/continue
2399e73e   Jean-Philippe Bernard   imprved towards r...
361
      message,'Known models are COMPIEGNE_ETAL2010,DBP90,DL01,DL07,AJ13,G17_MODELA,G17_MODELB,G17_MODELC,G17_MODELD,THEMIS',/continue
26361fb3   Jean-Philippe Bernard   improved
362
      stop
427f1205   Jean-Michel Glorian   version 4.2 merged
363
364
365
366
    END
  ENDCASE
ENDIF

bec7b3e8   Jean-Philippe Bernard   removed a stop
367
368
;stop

427f1205   Jean-Michel Glorian   version 4.2 merged
369
370
371
372
373
374
375
376
377
;Initialize !dustem_params structure
IF not keyword_set(dir) THEN BEGIN
;  CASE getenv('DUSTEM_WHICH') OF
  CASE !dustem_which OF
    'DESERT':dir_in=!dustem_wrap_soft_dir+'/Data/DESERT_POST_ISO_MORE/'
    'COMPIEGNE': dir_in=!dustem_wrap_soft_dir+'/Data/MC_DAT/'
;    'VERSTRAETE': dir_in=!dustem_wrap_soft_dir+'/Data/d_3.5/'
    'VERSTRAETE': dir_in=!dustem_wrap_soft_dir+'/Data/LV_DAT/'
    'WEB3p8': dir_in=!dustem_soft_dir
4fd64cbb   Ilyes Choubani   dustem_fit_sed_po...
378
    ELSE: dir_in=!dustem_wrap_soft_dir+'/Data/les_DAT/';!dustem_wrap_soft_dir+'/Data/les_DAT/'
427f1205   Jean-Michel Glorian   version 4.2 merged
379
380
381
382
383
384
385
  ENDCASE
ENDIF ELSE BEGIN
  dir_in=dir
ENDELSE
;stop
;dir_in=getenv('DUSTEM_SOFT_DIR')+'/src/'+dir
;dir_in=!dustem_soft_dir+'/src/'+dir
427f1205   Jean-Michel Glorian   version 4.2 merged
386

06fe3845   Ilyes Choubani   general update
387

1a82f397   Ilyes Choubani   Keep dustemwrap a...
388
if keyword_set(kwords) then defsysv, '!dustem_kwords', ptr_new(kwords) else defsysv, '!dustem_kwords', ptr_new()
06fe3845   Ilyes Choubani   general update
389
390
391

st_model=dustem_read_all(dir_in,/silent)
!dustem_params=ptr_new(st_model)
25a9c7a2   Ilyes Choubani   removing stops
392

3ff9cac3   Ilyes Choubani   general update
393

427f1205   Jean-Michel Glorian   version 4.2 merged
394
395
;=== create dynamical storage if needed
IF not file_test(!dustem_dat,/dir) THEN BEGIN
2cb867e5   Jean-Philippe Bernard   cant remember what
396
  spawn,'mkdir '+!dustem_dat
427f1205   Jean-Michel Glorian   version 4.2 merged
397
398
399
400
401
402
403
404
ENDIF
IF not file_test(!dustem_res,/dir) THEN BEGIN
  spawn,'mkdir '+!dustem_dat
ENDIF

;=== remove dynamical storage directories
;=== This is needed for iterative use of DUSTEM from IDL
if not keyword_set(noerase) then begin
427f1205   Jean-Michel Glorian   version 4.2 merged
405
406
407
408
409
410
411
412
413
414
CASE !dustem_which OF
  'VERSTRAETE':BEGIN
    IF file_test(!dustem_dat,/dir) THEN BEGIN
      spawn,'rm -rf '+!dustem_dat+'/les_DAT'
      spawn,'rm -rf '+!dustem_dat+'/les_QABS'
      spawn,'rm -rf '+!dustem_dat+'/les_CAPA'
    ENDIF
    IF file_test(!dustem_res,/dir) THEN BEGIN
      spawn,'rm -rf '+!dustem_res+'/les_RES'
    ENDIF
427f1205   Jean-Michel Glorian   version 4.2 merged
415
  END
4750086c   Ilyes Choubani   nouvelle philosph...
416
  'WEB3p8':BEGIN 
427f1205   Jean-Michel Glorian   version 4.2 merged
417
418
419
420
421
    IF file_test(!dustem_dat,/dir) THEN BEGIN
      spawn,'rm -rf '+!dustem_dat+'/data'
      spawn,'rm -rf '+!dustem_dat+'/hcap'
      spawn,'rm -rf '+!dustem_dat+'/oprop'
      spawn,'rm -rf '+!dustem_dat+'/out'
607060e5   Ilyes Choubani   test version
422
      ;spawn,'rm -rf '+!dustem_dat+'/plots' TO BE TESTED. NOT SURE ABOUT WHAT I AM DOING HERE. ASK JP ABOUT THIS
427f1205   Jean-Michel Glorian   version 4.2 merged
423
    ENDIF
427f1205   Jean-Michel Glorian   version 4.2 merged
424
425
426
427
428
429
430
  END
  ELSE: BEGIN
  END
ENDCASE

;=== create storage directories
;=== This is needed for iterative use of DUSTEM from IDL
427f1205   Jean-Michel Glorian   version 4.2 merged
431
432
433
434
435
436
437
438
439
440
CASE !dustem_which OF
  'VERSTRAETE':BEGIN
    IF file_test(!dustem_dat,/dir) THEN BEGIN
      spawn,'mkdir '+!dustem_dat+'/les_DAT'
      spawn,'mkdir '+!dustem_dat+'/les_QABS'
      spawn,'mkdir '+!dustem_dat+'/les_CAPA'
    ENDIF
    IF file_test(!dustem_res,/dir) THEN BEGIN
      spawn,'mkdir '+!dustem_res+'/les_RES'
    ENDIF
427f1205   Jean-Michel Glorian   version 4.2 merged
441
  END
e7938fa3   Ilyes Choubani   Corrected02: Impl...
442
  'WEB3p8':BEGIN  ; IN CHANGED THIS AS WELL
427f1205   Jean-Michel Glorian   version 4.2 merged
443
444
445
446
447
    IF file_test(!dustem_dat,/dir) THEN BEGIN
      spawn,'mkdir '+!dustem_dat+'/data'
      spawn,'mkdir '+!dustem_dat+'/hcap'
      spawn,'mkdir '+!dustem_dat+'/oprop'
      spawn,'mkdir '+!dustem_dat+'/out'
4750086c   Ilyes Choubani   nouvelle philosph...
448
      ;spawn,'mkdir '+!dustem_dat+'/plots' TO BE TESTED
427f1205   Jean-Michel Glorian   version 4.2 merged
449
    ENDIF
427f1205   Jean-Michel Glorian   version 4.2 merged
450
451
452
453
454
455
456
457
458
459
  END
  ELSE: BEGIN
  END
ENDCASE
endif ; /noerase

;=== If needed, test runing the model through the wrapper
IF keyword_set(wraptest) THEN BEGIN
  dir_out=!dustem_dat
  dustem_write_all,st_model,dir_out
36e8b879   Jean-Michel Glorian   update from deborah
460
 ; stop
427f1205   Jean-Michel Glorian   version 4.2 merged
461
462
463
464
465
466
467
468
469
470
471
472
  st=dustem_run()
  IF keyword_set(plot_it) THEN BEGIN
    loadct,13
    dustem_plot_nuinu_em,st,yr=[1e-14,1.e-6],/ysty,xr=[1,5e3],/xsty
  ENDIF
ENDIF

;stop

;Initialize filters
dustem_filter_init,dir=dir

68598bce   Ilyes Choubani   reducing number o...
473

427f1205   Jean-Michel Glorian   version 4.2 merged
474
475
476
the_end:

END