Blame view

src/idl/dustem_cc.pro 10.4 KB
14188148   Jean-Philippe Bernard   improved
1
FUNCTION dustem_cc,wavein,spec,filter_names,cc=cc,fluxconv=fluxconv,no_sort=no_sort,help=help
427f1205   Jean-Michel Glorian   version 4.2 merged
2
3
4
5

;+
; NAME:
;    dustem_cc
1e005c88   Annie Hughes   inlie help
6
;
427f1205   Jean-Michel Glorian   version 4.2 merged
7
; PURPOSE:
1e005c88   Annie Hughes   inlie help
8
9
;    Computes observed SED and color correction for a given spectrum in a given filter
;
427f1205   Jean-Michel Glorian   version 4.2 merged
10
; CATEGORY:
1e005c88   Annie Hughes   inlie help
11
12
;    DustEMWrap, Mid-Level, Distributed, Color corrections
;
427f1205   Jean-Michel Glorian   version 4.2 merged
13
14
; CALLING SEQUENCE:
;    sed=dustem_cc(wave,spec,filter_names,cc=cc,fluxconv=fluxconv,help=help)
1e005c88   Annie Hughes   inlie help
15
;
427f1205   Jean-Michel Glorian   version 4.2 merged
16
17
18
; INPUTS:
;    wave: array of wavelengths for spec
;    spec: spectrum (must be in brightness units)
1e005c88   Annie Hughes   inlie help
19
20
21
;    filter_names: names of filters for which color correction is
;    needed
;  
427f1205   Jean-Michel Glorian   version 4.2 merged
22
23
; OPTIONAL INPUT PARAMETERS:
;    None
1e005c88   Annie Hughes   inlie help
24
;
427f1205   Jean-Michel Glorian   version 4.2 merged
25
26
; OUTPUTS:
;    sed: SED as observed in filters provided in filter_names
1e005c88   Annie Hughes   inlie help
27
;
427f1205   Jean-Michel Glorian   version 4.2 merged
28
29
; OPTIONAL OUTPUT PARAMETERS:
;    cc        = color correction coefficients (spec*cc=sed)
1e005c88   Annie Hughes   inlie help
30
;
427f1205   Jean-Michel Glorian   version 4.2 merged
31
32
; ACCEPTED KEY-WORDS:
;    fluxconv  = if set, these are taken for flux conventions
ab47fb7c   Annie Hughes   added NIKA2
33
34
;              possible values: 'nuInu=cste', 'FLAMBDA=cste', 'FLAMBDA=cste'
;              , 'IRAC', 'MIPS', 'CMB', 'HFI', 'LABOCA', 'NIKA2'
14188148   Jean-Philippe Bernard   improved
35
;    no_sort   = if set, input arrauys are assumed to already be orderd by increasing wavelengths
427f1205   Jean-Michel Glorian   version 4.2 merged
36
;    help      = If set, print this help
1e005c88   Annie Hughes   inlie help
37
;
427f1205   Jean-Michel Glorian   version 4.2 merged
38
39
; COMMON BLOCKS:
;    None
1e005c88   Annie Hughes   inlie help
40
;
427f1205   Jean-Michel Glorian   version 4.2 merged
41
42
; SIDE EFFECTS:
;    None
1e005c88   Annie Hughes   inlie help
43
;
427f1205   Jean-Michel Glorian   version 4.2 merged
44
; RESTRICTIONS:
997bd805   Annie Hughes   comments and gene...
45
46
;    The DustEM fortran code must be installed
;    The DustEMWrap IDL code must be installed
1e005c88   Annie Hughes   inlie help
47
;
427f1205   Jean-Michel Glorian   version 4.2 merged
48
49
; PROCEDURE:
;    None
1e005c88   Annie Hughes   inlie help
50
;
427f1205   Jean-Michel Glorian   version 4.2 merged
51
52
53
; EXAMPLES
;    
; MODIFICATION HISTORY:
997bd805   Annie Hughes   comments and gene...
54
55
56
;    Written JPB Apr-2011
;    Evolution details on the DustEMWrap gitlab.
;    See http://dustemwrap.irap.omp.eu/ for FAQ and help.  
427f1205   Jean-Michel Glorian   version 4.2 merged
57
58
;-

427f1205   Jean-Michel Glorian   version 4.2 merged
59
60
61
62
63
64
65
66
IF keyword_set(help) THEN BEGIN
  doc_library,'dustem_cc'
  sed=0.
  goto,the_end
ENDIF

;eps=1.e-30
eps=0.
997bd805   Annie Hughes   comments and gene...
67
68

;=== constants needed for CMB flux convention
427f1205   Jean-Michel Glorian   version 4.2 merged
69
70
Tcmb=2.725D0

997bd805   Annie Hughes   comments and gene...
71
;=== constants needed for MIPS flux convention
427f1205   Jean-Michel Glorian   version 4.2 merged
72
73
74
75
76
h=6.62606876*1d-34            ; J s
c=2.99792458*1d8              ; m*s-1
K=1.380658*1d-23              ; J/K 
T_0=1d4                       ; calibration star (K units)
fact=h*c
427f1205   Jean-Michel Glorian   version 4.2 merged
77
78
fact3=K*T_0

14188148   Jean-Philippe Bernard   improved
79
80
81
82
83
84
85
86
87
;sort input, unles /no_sort
IF not keyword_set(no_sort) THEN BEGIN
  order =sort(wavein)
  spec2 = [eps,spec[order]]
  wavein2 = [eps,wavein[order]]
ENDIF ELSE BEGIN
  wavein2=wavein
  spec2=spec
ENDELSE
427f1205   Jean-Michel Glorian   version 4.2 merged
88
89
90
91
92
93
94
95
96
97

IF not keyword_set(fluxconv) THEN BEGIN
  fluxconvs=dustem_filter2fluxconv(filter_names)
ENDIF ELSE BEGIN
  fluxconvs=fluxconv
ENDELSE
instrus=dustem_filter2instru(filter_names)

inst_tags=tag_names((*!dustem_filters))

427f1205   Jean-Michel Glorian   version 4.2 merged
98
99
100
101
102
103
104
105
Nbands=n_elements(filter_names)
sed=dblarr(Nbands)

cc=dblarr(Nbands)
cc(*)=1.d0

FOR i=0L,Nbands-1 DO BEGIN
  iinstru=where(inst_tags EQ instrus(i),countinstr)
b5ccb706   Jean-Philippe Bernard   improved to fit p...
106
107
108
109
  IF countinstr EQ 0 THEN BEGIN
    message,'Instrument '+instrus(i)+' not found',/continue
    stop
  ENDIF
427f1205   Jean-Michel Glorian   version 4.2 merged
110
  st=(*!dustem_filters).(iinstru)
4caf5d4a   Annie Hughes   changes for JWST ...
111
112
;  stop
  ii=(where(st.filter_names EQ filter_names[i]))[0]
997bd805   Annie Hughes   comments and gene...
113
  spec0=interpol(spec2,wavein2,st.central_wavelengths[ii])
cc7d8a09   Jean-Philippe Bernard   changed
114
115
116
117
118
  IF spec0 EQ 0 THEN BEGIN
    sed[i]=spec0
    cc[i]=1
    goto,next_filter
  ENDIF
997bd805   Annie Hughes   comments and gene...
119
  IF !dustem_do_cc NE 0 and not !dustem_never_do_cc THEN BEGIN ;Color corrections are computed
427f1205   Jean-Michel Glorian   version 4.2 merged
120
;    print,'DOING color correction calculations'
997bd805   Annie Hughes   comments and gene...
121
    CASE strupcase(fluxconvs[i]) OF
427f1205   Jean-Michel Glorian   version 4.2 merged
122
      'HFI0': BEGIN  ;This is purely for test (stupid since reads filters each time)
ab47fb7c   Annie Hughes   added NIKA2
123
         filter_dir=!dustem_wrap_soft_dir+'/Data/FILTERS/'
427f1205   Jean-Michel Glorian   version 4.2 merged
124
125
126
127
128
        dir_hfi=filter_dir+'HFI/OFFICIAL'+'/'
;       CAUTION: This below should be consistent with what is in dustem_read_filters.pro
;        hfi_filter_version='v101'
        hfi_filter_version='v201'
        bp = hfi_read_bandpass(hfi_filter_version, /rimo,path_rimo=dir_hfi)
997bd805   Annie Hughes   comments and gene...
129
        spec_int=interpol(spec2,wavein2,*(st.use_wavelengths[ii]))
427f1205   Jean-Michel Glorian   version 4.2 merged
130
131
132
133
134
135
136
137
        nu=*(st.use_frequencies(ii))/1.d9
        order=sort(nu)
        spec_int=spec_int(order)
        nu=nu(order)
        channel=strtrim(round(dustem_filter2freq(filter_names(i))),2)
;stop
        ccc=hfi_color_correction_dustem(bp.name,bp.freq/1.d9,bp.trans,channel, bolo_cc,nu, spec_int)
;        ccc=hfi_color_correction(bp,channel, bolo_cc,nu, spec_int)
cc7d8a09   Jean-Philippe Bernard   changed
138
        cc[i]=ccc.cc
427f1205   Jean-Michel Glorian   version 4.2 merged
139
140
      END
      'HFI': BEGIN
ab47fb7c   Annie Hughes   added NIKA2
141
142
143
144
145
146
147
148
149
150
151
152
         spec_int=interpol(spec2,wavein2,*(st.use_wavelengths(ii)))
         nu=*(st.use_frequencies(ii))/1.d9
         trans=*(st.use_transmissions(ii))
         order=sort(nu)
         spec_int=spec_int(order)
         nu=nu(order)
         trans=trans(order)
         channel=strtrim(round(dustem_filter2freq(filter_names(i))),2)
         ccc=hfi_color_correction_dustem(channel,nu,trans,channel, bolo_cc,nu, spec_int)
         cc[i]=ccc.cc
      END
      'FNU=CSTE': BEGIN
2a89c8d9   Jean-Philippe Bernard   modified to compu...
153
         ;beta=0.
ab47fb7c   Annie Hughes   added NIKA2
154
155
         spec_int=interpol(spec2,wavein2,*(st.use_wavelengths[ii]))
         num=integral(*(st.use_wavelengths[ii]),spec_int*(*(st.use_transmissions[ii]))/(*(st.use_wavelengths[ii]))^2.,st.use_wmin[ii],st.use_wmax[ii],/double)
2a89c8d9   Jean-Philippe Bernard   modified to compu...
156
157
158
         ;den=integral(*(st.use_wavelengths(ii)),((*(st.use_transmissions(ii)))/((*(st.use_wavelengths(ii)))^(2+beta))),st.use_wmin(ii),st.use_wmax(ii),/double)               
         ;cc[i]=num/(spec0*den*(st.central_wavelengths[ii])^beta)
         cc[i]=num/(spec0*st.filters_integral[ii])
427f1205   Jean-Michel Glorian   version 4.2 merged
159
160
      END
      'NUINU=CSTE': BEGIN
2a89c8d9   Jean-Philippe Bernard   modified to compu...
161
         ;beta=-1.
109b7cd3   Annie Hughes   added flambda=cste
162
163
         spec_int=interpol(spec2,wavein2,*(st.use_wavelengths(ii)))
         num=integral(*(st.use_wavelengths(ii)),spec_int*(*(st.use_transmissions(ii)))/(*(st.use_wavelengths(ii)))^2.,st.use_wmin(ii),st.use_wmax(ii),/double)
2a89c8d9   Jean-Philippe Bernard   modified to compu...
164
165
166
         ;den=integral(*(st.use_wavelengths(ii)),((*(st.use_transmissions(ii)))/((*(st.use_wavelengths(ii)))^(2+beta))),st.use_wmin(ii),st.use_wmax(ii),/double)               
         ;cc[i]=num/(spec0*den*(st.central_wavelengths[ii])^beta)
         cc[i]=num/(spec0*st.filters_integral[ii])
109b7cd3   Annie Hughes   added flambda=cste
167
168
      END
      'FLAMBDA=CSTE': BEGIN
2a89c8d9   Jean-Philippe Bernard   modified to compu...
169
         ;beta=-2.
4caf5d4a   Annie Hughes   changes for JWST ...
170
171
         spec_int=interpol(spec2,wavein2,*(st.use_wavelengths[ii]))
         num=integral(*(st.use_wavelengths[ii]),spec_int*(*(st.use_transmissions[ii]))/(*(st.use_wavelengths[ii]))^2.,st.use_wmin[ii],st.use_wmax[ii],/double)
2a89c8d9   Jean-Philippe Bernard   modified to compu...
172
         ;den=integral(*(st.use_wavelengths(ii)),((*(st.use_transmissions(ii)))/((*(st.use_wavelengths(ii)))^(2+beta))),st.use_wmin(ii),st.use_wmax(ii),/double)               
ab47fb7c   Annie Hughes   added NIKA2
173
174
;         den=integral(*(st.use_wavelengths[ii]),(*(st.use_transmissions[ii])),st.use_wmin[ii],st.use_wmax[ii],/double)
;         cc[i]=(num*(st.central_wavelengths[ii])^2)/(spec0*den)
2a89c8d9   Jean-Philippe Bernard   modified to compu...
175
176
         ;cc[i]=num/(spec0*den*(st.central_wavelengths[ii])^beta)
         cc[i]=num/(spec0*st.filters_integral[ii])
427f1205   Jean-Michel Glorian   version 4.2 merged
177
      END
2a89c8d9   Jean-Philippe Bernard   modified to compu...
178
179
      'MIPS': BEGIN ;Not used ??
        ;expon=exp(fact/(*(st.use_wavelengths(ii))*1e-6*fact3))-1.
427f1205   Jean-Michel Glorian   version 4.2 merged
180
181
        spec_int=interpol(spec2,wavein2,*(st.use_wavelengths(ii)))
        num=integral(*(st.use_wavelengths(ii)),spec_int*(*(st.use_transmissions(ii)))/(*(st.use_wavelengths(ii)))^2.,st.use_wmin(ii),st.use_wmax(ii),/double)
2a89c8d9   Jean-Philippe Bernard   modified to compu...
182
183
184
185
        ;den=integral(*(st.use_wavelengths(ii)),*(st.use_transmissions(ii))/(*(st.use_wavelengths(ii)))^5/expon,st.use_wmin(ii),st.use_wmax(ii),/double)
        ;ffact=st.central_wavelengths(ii)*1e-6*K*T_0
        ;cc[i]=num/den/spec0/(st.central_wavelengths(ii))^3/(exp(fact/ffact)-1.)
        cc[i]=num/(spec0*st.filters_integral[ii])
427f1205   Jean-Michel Glorian   version 4.2 merged
186
187
188
189
      END
      'IRAC': BEGIN
        spec_int=interpol(spec2,wavein2,*(st.use_wavelengths(ii)))
        num=integral(*(st.use_wavelengths(ii)),spec_int*(*(st.use_transmissions(ii)))/(*(st.use_wavelengths(ii))),st.use_wmin(ii),st.use_wmax(ii),/double)
2a89c8d9   Jean-Philippe Bernard   modified to compu...
190
191
192
193
        ;den=integral(*(st.use_wavelengths(ii)),*(st.use_transmissions(ii)),st.use_wmin(ii),st.use_wmax(ii),/double)
        ;cc[i]=num/den/spec0*(st.central_wavelengths(ii))
        cc[i]=num/(spec0*st.filters_integral[ii])
       END
427f1205   Jean-Michel Glorian   version 4.2 merged
194
195
196
      'CMB': BEGIN
        spec_int=interpol(spec2,wavein2,*(st.use_wavelengths(ii)))
        num=integral(*(st.use_wavelengths(ii)),spec_int*(*(st.use_transmissions(ii)))/(*(st.use_wavelengths(ii)))^2.,st.use_wmin(ii),st.use_wmax(ii),/double)
2a89c8d9   Jean-Philippe Bernard   modified to compu...
197
198
199
        ;den=integral(*(st.use_wavelengths(ii)),(*(st.use_transmissions(ii)))/(*(st.use_wavelengths(ii))^2)*dustem_planck_function(Tcmb,*(st.use_wavelengths(ii))),st.use_wmin(ii),st.use_wmax(ii),/double)
        ;cc[i]=num/den*dustem_planck_function(Tcmb,st.central_wavelengths(ii))/spec0
        cc[i]=num/(spec0*st.filters_integral[ii])
427f1205   Jean-Michel Glorian   version 4.2 merged
200
201
202
203
204
205
     END
      'LABOCA': BEGIN
;        spec_int=interpol(spec2,wavein2,*(st.use_wavelengths(ii)))
;        num=integral(*(st.use_wavelengths(ii)),spec_int*(*(st.use_transmissions(ii))),st.use_wmin(ii),st.use_wmax(ii),/double)
;        den=integral(*(st.use_wavelengths(ii)),*(st.use_transmissions(ii))/(*(st.use_wavelengths(ii))^2.5),st.use_wmin(ii),st.use_wmax(ii),/double)
;        cc(i)=num/den/spec0/(st.central_wavelengths(ii))^2.5
b5ccb706   Jean-Philippe Bernard   improved to fit p...
206
        alpha_new=0.
427f1205   Jean-Michel Glorian   version 4.2 merged
207
208
        spec_int=interpol(spec2,wavein2,*(st.use_wavelengths(ii)))
        num=integral(*(st.use_wavelengths(ii)),spec_int*(*(st.use_transmissions(ii)))/(*(st.use_wavelengths(ii))),st.use_wmin(ii),st.use_wmax(ii),/double)
2a89c8d9   Jean-Philippe Bernard   modified to compu...
209
210
211
        ;den=integral(*(st.use_wavelengths(ii)),*(st.use_transmissions(ii))/(*(st.use_wavelengths(ii))^(alpha_new+2.)),st.use_wmin(ii),st.use_wmax(ii),/double)
        ;cc[i]=num/den/spec0*(st.central_wavelengths(ii))^(-(alpha_new+1.))
        cc[i]=num/(spec0*st.filters_integral[ii])
ab47fb7c   Annie Hughes   added NIKA2
212
213
      END
      'NIKA2': BEGIN
2a89c8d9   Jean-Philippe Bernard   modified to compu...
214
         ;beta=1.6 
ab47fb7c   Annie Hughes   added NIKA2
215
216
         spec_int=interpol(spec2,wavein2,*(st.use_wavelengths(ii)))
         num=integral(*(st.use_wavelengths(ii)),spec_int*(*(st.use_transmissions(ii)))/(*(st.use_wavelengths(ii)))^2.,st.use_wmin(ii),st.use_wmax(ii),/double)
2a89c8d9   Jean-Philippe Bernard   modified to compu...
217
218
219
         ;den=integral(*(st.use_wavelengths(ii)),((*(st.use_transmissions(ii)))/((*(st.use_wavelengths(ii)))^(2+beta))),st.use_wmin(ii),st.use_wmax(ii),/double)               
         ;cc[i]=num/(spec0*den*(st.central_wavelengths[ii])^beta)
         cc[i]=num/(spec0*st.filters_integral[ii])
427f1205   Jean-Michel Glorian   version 4.2 merged
220
      END
b5ccb706   Jean-Philippe Bernard   improved to fit p...
221
      ELSE:BEGIN
8a78e3bd   Annie Hughes   changed default b...
222
223
        message,strupcase(fluxconvs[i])+' not recognized, assuming NUINU=CSTE',/info
        ;cc[i]=1. ; changed default behaviour in version 4.3
2a89c8d9   Jean-Philippe Bernard   modified to compu...
224
         ;beta=-1.
8a78e3bd   Annie Hughes   changed default b...
225
226
         spec_int=interpol(spec2,wavein2,*(st.use_wavelengths(ii)))
         num=integral(*(st.use_wavelengths(ii)),spec_int*(*(st.use_transmissions(ii)))/(*(st.use_wavelengths(ii)))^2.,st.use_wmin(ii),st.use_wmax(ii),/double)
2a89c8d9   Jean-Philippe Bernard   modified to compu...
227
228
229
         ;den=integral(*(st.use_wavelengths(ii)),((*(st.use_transmissions(ii)))/((*(st.use_wavelengths(ii)))^(2+beta))),st.use_wmin(ii),st.use_wmax(ii),/double)               
         ;cc[i]=num/(spec0*den*(st.central_wavelengths[ii])^beta)
         cc[i]=num/(spec0*st.filters_integral[ii])
b5ccb706   Jean-Philippe Bernard   improved to fit p...
230
      END
427f1205   Jean-Michel Glorian   version 4.2 merged
231
232
233
234
235
236
237
    ENDCASE
    !dustem_previous_cc=ptr_new(cc)
  ENDIF ELSE BEGIN ;When no new cc calculation is required
    IF !dustem_never_do_cc EQ 0 THEN BEGIN
      cc=(*!dustem_previous_cc)
    ENDIF
  ENDELSE
9074d6cd   Jean-Philippe Bernard   fixed a bug of Na...
238
  IF finite(cc[i]) THEN sed[i]=spec0*cc[i] ELSE sed[i]=spec0
cc7d8a09   Jean-Philippe Bernard   changed
239
  next_filter:
427f1205   Jean-Michel Glorian   version 4.2 merged
240
241
242
243
244
245
ENDFOR

the_end:
RETURN,sed

END