Blame view

src/idl/dustem_mask_data.pro 11.1 KB
88872c38   Ilyes Choubani   small update. Cha...
1
2
3
4
5
6
FUNCTION dustem_mask_data, data_struct,       $
                           filters,           $
                           data_set=data_set, $
                           default=default,   $
                           help=help

11e52e98   Ilyes Choubani   corrected to incl...
7
8
9
10
;+
; NAME:
;    dustem_mask_data
; PURPOSE:
88872c38   Ilyes Choubani   small update. Cha...
11
;    Set dataset values to la_undef() for specified filter/spectrum data in an input DustEmWrap data structure.
11e52e98   Ilyes Choubani   corrected to incl...
12
13
14
; CATEGORY:
;    DUSTEM Wrapper
; CALLING SEQUENCE:
88872c38   Ilyes Choubani   small update. Cha...
15
;    data_struct=dustem_mask_data(data_struct,filters,data_set=,/default)
11e52e98   Ilyes Choubani   corrected to incl...
16
; INPUTS:
88872c38   Ilyes Choubani   small update. Cha...
17
18
19
20
21
22
23
;    data_struct : SED Data structure following the format explained in the DustermWrap Users' Guide
;
;    filters : Can be an array or list. In both cases it should contain the filter names as character strings. 
;    ie: filters=['SPIRE1','SPIRE2'] for an array or filters=list(['SPIRE2','SPIRE1','PACS2'],['HFI5','HFI4']) for a list.
;    When using a list, its shape (dimension) and the number of elements of the data_set array should be equal.
;    Each dimension is an array of filters to be removed from the corresponding data set in the data_set array.
;    ie: filters=list(['SPIRE2','SPIRE1','PACS2'],['LFI2','LFI3']) for datas_set=['STOKESI','STOKESQ']
11e52e98   Ilyes Choubani   corrected to incl...
24
; OPTIONAL INPUT PARAMETERS:
88872c38   Ilyes Choubani   small update. Cha...
25
26
;    data_set : Array of character strings containing the different data sets to be filtered.
;    ie: ['STOKESI','STOKESQ','STOKESU'] or just ['STOKESQ'] for example.
11e52e98   Ilyes Choubani   corrected to incl...
27
28
29
30
31
; OUTPUTS:
;    data_struct 
; OPTIONAL OUTPUT PARAMETERS:
;    None
; ACCEPTED KEY-WORDS:
88872c38   Ilyes Choubani   small update. Cha...
32
33
34
35
36
;    help                  = if set, print this help
;
;    default               = if set, remove targeted filter/spectrum point(s) from datasets that depend on the filtered dataset(s).
; EAMPLE
;    masked_structure = dustem_mask_data(data_struct,['IRAS1','IRAS2'],data_set=['STOKESI'])  
11e52e98   Ilyes Choubani   corrected to incl...
37
; COMMENTS
88872c38   Ilyes Choubani   small update. Cha...
38
39
40
41
42
;    IC:
;    If a wavelength value is supplied instead of a filter name, the procedure masks for a spectrum point with that corresponding wavelength
;    If the dataset array isn't supplied, all the datasets in the input data structure will be considered.
;    If both filters and dataset are arrays, all mentioned filters will be masked from all mentioned datasets.
;    This procedure does not change the shape of the output structure partly because dustem_check_data.pro does.
11e52e98   Ilyes Choubani   corrected to incl...
43
; MODIFICATION HISTORY:
88872c38   Ilyes Choubani   small update. Cha...
44
;    Written by IC 2022
11e52e98   Ilyes Choubani   corrected to incl...
45
;-
11a73ecb   Ilyes Choubani   The filtering/mas...
46
47
48


IF keyword_set(help) THEN BEGIN
88872c38   Ilyes Choubani   small update. Cha...
49
  doc_library,'dustem_mask_data'
11a73ecb   Ilyes Choubani   The filtering/mas...
50
51
52
  goto,the_end
ENDIF

88872c38   Ilyes Choubani   small update. Cha...
53
IF arg_present(data_struct) and arg_present(filters) THEN BEGIN
11a73ecb   Ilyes Choubani   The filtering/mas...
54
    
88872c38   Ilyes Choubani   small update. Cha...
55
56
    ;Array of filters present in dustem
    filters_dustem=[((*!dustem_filters).(0).filter_names)]    
11a73ecb   Ilyes Choubani   The filtering/mas...
57
58
59
    for i=1L,n_elements(tag_names(*!dustem_filters))-1 do begin
        filters_dustem=[filters_dustem,((*!dustem_filters).(i).filter_names)] 
    endfor 
11a73ecb   Ilyes Choubani   The filtering/mas...
60
61
    ;Array of filters present in data_struct
    filters_data = data_struct.filter
11a73ecb   Ilyes Choubani   The filtering/mas...
62
    ;Tag names present in data_struct (to be able to test on the different data sets)
88872c38   Ilyes Choubani   small update. Cha...
63
64
    tagnames = tag_names(data_struct)    
    if typename(filters) EQ 'LIST' then ind0 = filters[*] else ind0=intarr(n_elements(filters))
11a73ecb   Ilyes Choubani   The filtering/mas...
65
    ;because types can be float or double but not long. 
88872c38   Ilyes Choubani   small update. Cha...
66
67
    for i=0L,n_elements(filters)-1 do begin
        dim_i = n_elements(filters(i)) ;getting the dimension of each element of the list/array
11a73ecb   Ilyes Choubani   The filtering/mas...
68
        ind0[i] = intarr(dim_i) + la_undef() ;initializing to la_undef()     
88872c38   Ilyes Choubani   small update. Cha...
69
    endfor    
11a73ecb   Ilyes Choubani   The filtering/mas...
70
    ;Gathering the indices of the filters to remove.        
88872c38   Ilyes Choubani   small update. Cha...
71
72
73
    for i=0L,n_elements(filters)-1 do begin        
        dim_i=n_elements(filters(i)) ;Getting the dimension of each element of the list
        arr_i=intarr(dim_i) + la_undef() ;initializing to la_undef()        
11a73ecb   Ilyes Choubani   The filtering/mas...
74
        for j=0L,dim_i-1 do begin
11a73ecb   Ilyes Choubani   The filtering/mas...
75
            ;testing whether the element corresponds to a specific wavelength. 
88872c38   Ilyes Choubani   small update. Cha...
76
77
78
79
80
81
82
83
84
            ;accepts both numbers/strings          
            if valid_num((filters[i])[j]) then begin               
                ind=where(float((filters[i])[j]) EQ data_struct.wave,test0)
                if test0 ne 0 and data_struct[ind].filter EQ 'SPECTRUM' then arr_i[j] = ind else message, 'WAVELENGTH '+strtrim((filters[i])[j],2)+' does not correspond to any spectrum point in the supplied data strucure.'
            endif else begin  
                ind = where((filters[i])[j] EQ filters_dustem,test1) 
                if test1 eq 0 then message, "Filter "+strtrim((filters[i])[j],2)+" isn't in the DustEMWrap Filters' list"
                ind = where((filters[i])[j] EQ filters_data,test2) ;Test if the filter in in the data itself
                if test2 ne 0 then arr_i[j] = ind else message, 'Filter '+strtrim((filters[i])[j],2)+' cannot be found in the supplied data structure.'              
11a73ecb   Ilyes Choubani   The filtering/mas...
85
            endelse
88872c38   Ilyes Choubani   small update. Cha...
86
        endfor        
11a73ecb   Ilyes Choubani   The filtering/mas...
87
        ind0[i] = arr_i ;Indices of the filters to be removed in the data structure
11a73ecb   Ilyes Choubani   The filtering/mas...
88
    endfor
0068116a   Ilyes Choubani   General update + ...
89
    
88872c38   Ilyes Choubani   small update. Cha...
90
91
92
93
94
    If typename(ind0) EQ 'LIST' then indices = ind0[i] ELSE indices = ind0 
     
     ;If default isn't set, errors in dustem_check_data.pro can occur because of differences in tag values. A common behavior of dustem_check_data.pro
     ;example: filter removed for StokesI but not for SIGMAII
    IF keyword_set(default) THEN BEGIN
0068116a   Ilyes Choubani   General update + ...
95
        
88872c38   Ilyes Choubani   small update. Cha...
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
        ;Part pertainig to the /default keyword
        ;bunch of tests to locate datasets depending on STOKESI, STOKESQ, STOKESU, LARGEP, SMALLP and PSI     
        ;is it an emission or extinction structure?
        ind_m = where(tagnames EQ 'STOKESI', ctm)
        ind_x = where(tagnames EQ 'EXT_I', ctx)
        IF ctm NE 0 THEN BEGIN ;no counters are used in the following because it's a consequence of the test being valid.
            ;Getting the indices this way because it allows for an easy modification if/when tagnames in the xcat emission/extinction file change
            ind_set_StokesI =  fix([where(strmatch(tagnames,'STOKESI')), $
                                 where(strmatch(tagnames,'SIGMAII'))]) 
            ind_set_StokesQ = fix([where(strmatch(tagnames,'STOKESQ')),  $ 
                                where(strmatch(tagnames,'SIGMAQQ')),     $
                                where(strmatch(tagnames,'SIGMAIQ')) ])
            ind_set_StokesU = fix([where(strmatch(tagnames,'STOKESU')),  $ 
                                where(strmatch(tagnames,'SIGMAUU')),     $
                                where(strmatch(tagnames,'SIGMAIU')) ])
            ind_set_LargeP = fix([where(strmatch(tagnames,'LARGEP')),    $
                                where(strmatch(tagnames,'SIGMA_LARGEP'))])
            ind_set_smallp = fix([where(strmatch(tagnames,'SMALLP')),    $
                               where(strmatch(tagnames,'SIGMA_SMALLP'))])
            ind_set_psi = fix([where(strmatch(tagnames,'PSI')),          $
                            where(strmatch(tagnames,'SIGMA_PSI'))])                    
        ENDIF
        IF ctx NE 0 THEN BEGIN
            ind_set_EXT_I =  fix([where(strmatch(tagnames,'EXT_I')),          $ 
                               where(strmatch(tagnames,'SIGEXTII')) ]) 
            ind_set_EXT_Q = fix([where(strmatch(tagnames,'EXT_Q')),           $
                              where(strmatch(tagnames,'SIGEXTQQ')),           $
                              where(strmatch(tagnames,'SIGEXTIQ')) ])  
            ind_set_EXT_U = fix([where(strmatch(tagnames,'EXT_U')),           $
                              where(strmatch(tagnames,'SIGEXTUU')),           $
                              where(strmatch(tagnames,'SIGEXTIU')) ]) 
            ind_set_EXT_P = fix([where(strmatch(tagnames,'EXT_P')),           $
                              where(strmatch(tagnames,'SIGEXTP'))])
            ind_set_EXT_smallp = fix([where(strmatch(tagnames,'EXT_SMALLP')), $
                                   where(strmatch(tagnames,'SIGEXTSMALLP'))])
            ind_set_psi = fix([where(strmatch(tagnames,'PSI')),               $
                            where(strmatch(tagnames,'SIGEXTPSI'))])
        ENDIF
    ENDIF
   
    ;setting filters' data to la_undef()    
11a73ecb   Ilyes Choubani   The filtering/mas...
137
    IF keyword_set(data_set) then begin
0068116a   Ilyes Choubani   General update + ...
138
            
88872c38   Ilyes Choubani   small update. Cha...
139
140
        FOR i=0L,n_elements(data_set)-1 DO BEGIN
            ind_set = where(tagnames EQ data_set(i),ctset)
11a73ecb   Ilyes Choubani   The filtering/mas...
141
            if ctset ne 0 then begin
11a73ecb   Ilyes Choubani   The filtering/mas...
142
            
88872c38   Ilyes Choubani   small update. Cha...
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
                ;the requires the default keyword to be set
                IF keyword_set(default)  THEN BEGIN    
                    ;EMISSION CASE
                    IF ctm NE 0 THEN BEGIN
                        ;testing data_set(i) against the above strings. 
                        test_StokesI = where(ind_set_StokesI EQ ind_set, ct_StokesI)
                        IF ct_StokesI NE 0 THEN data_struct(indices).(ind_set_StokesI) = la_undef()
                        test_StokesQ =  where(ind_set_StokesQ EQ ind_set, ct_StokesQ)
                        IF ct_StokesQ NE 0 THEN data_struct(indices).(ind_set_StokesQ) = la_undef()
                        test_StokesU = where(ind_set_StokesU EQ ind_set, ct_StokesU)
                        IF ct_StokesU NE 0 THEN data_struct(indices).(ind_set_StokesU) = la_undef()
                        test_LargeP = where(ind_set_LargeP EQ ind_set, ct_LargeP)
                        IF ct_LargeP NE 0 THEN data_struct(indices).(ind_set_LargeP) = la_undef()
                        test_smallp = where(ind_set_smallp EQ ind_set, ct_smallp)
                        IF ct_smallp NE 0 THEN data_struct(indices).(ind_set_smallp) = la_undef()
                        test_psi = where(ind_set_psi EQ ind_set, ct_psi)
                        IF ct_psi NE 0 THEN data_struct(indices).(ind_set_psi) = la_undef()
                    ENDIF     
                    ;EXTINCTION CASE
                    IF ctx NE 0 THEN BEGIN
                        ;testing data_set(i) against the above strings. 
                        test_EXT_I = where(ind_set_EXT_I EQ ind_set, ct_EXT_I)
                        IF ct_EXT_I NE 0 THEN data_struct(indices).(ind_set_EXT_I) = la_undef()
                        test_EXT_Q =  where(ind_set_EXT_Q EQ ind_set, ct_EXT_Q)
                        IF ct_EXT_Q NE 0 THEN data_struct(indices).(ind_set_EXT_Q) = la_undef()
                        test_EXT_U = where(ind_set_EXT_U EQ ind_set, ct_EXT_U)
                        IF ct_EXT_U NE 0 THEN data_struct(indices).(ind_set_EXT_U) = la_undef()
                        test_EXT_P = where(ind_set_EXT_P EQ ind_set, ct_EXT_P)
                        IF ct_EXT_P NE 0 THEN data_struct(indices).(ind_set_EXT_P) = la_undef()
                        test_EXT_smallp = where(ind_set_EXT_smallp EQ ind_set, ct_EXT_smallp)
                        IF ct_EXT_smallp NE 0 THEN data_struct(indices).(ind_set_EXT_smallp) = la_undef()
                        test_psi = where(ind_set_psi EQ ind_set, ct_psi)
                        IF ct_psi NE 0 THEN data_struct(indices).(ind_set_psi) = la_undef()
                    ENDIF         
                ENDIF ELSE data_struct(indices).(ind_set) = la_undef()            
            ENDIF
        ENDFOR
    ENDIF ELSE BEGIN ;If no datasets are supplied, all tag values are set to la_undef()
11a73ecb   Ilyes Choubani   The filtering/mas...
181
        ind_tags = where(tagnames ne 'INSTRU' and tagnames ne 'FILTER' and tagnames ne 'WAVE')
88872c38   Ilyes Choubani   small update. Cha...
182
183
184
        FOR j=0L,n_elements(ind_tags)-1 DO BEGIN
            data_struct(indices).(ind_tags(j)) = la_undef()               
        ENDFOR 
11a73ecb   Ilyes Choubani   The filtering/mas...
185
    endelse
11a73ecb   Ilyes Choubani   The filtering/mas...
186
187
ENDIF ELSE message, 'Cannot proceed. Keyword(s) missing. Refer to help for keyword options.'

88872c38   Ilyes Choubani   small update. Cha...
188
RETURN, data_struct
11a73ecb   Ilyes Choubani   The filtering/mas...
189
190
191
192
the_end:


END