Skip to content
Snippets Groups Projects
cws_read__readdata.pro 55.92 KiB
; $Id:$
;+
; FUNCTION cws_read::readData
;
; Purpose: 
;   read data in the original format of the groups
;   returns the data/image to read
; 
; input
; version: in, optional, type=string
;                 specifies the version of the data 
;                 night be 'CREW2' or 'CREW3'
;                 !!! this a first attempt to estabish this
;                 functionality !!!
;- 

FUNCTION cws_read::readData, version=version

   COMMON FEEDBACK, quiet, verbose, debug
   ;-------------------------------------

   ; default for data version 
   if n_elements(version) eq 0 then version = 'icwg2'

   IF not quiet THEN PRINT, '... read '+ self.product +' for group '+ self.grp+' (cws_read__readdata.pro)'

   if strLowCase(STRMID(self.product,0,1)) eq 'u' then uncertainty=1

   CASE self.grp OF
      'TPS':begin
          return,self.readData_TPS()
      end
      
      'KNM':BEGIN
          return,self.readdata_KNM()
      END
      
      ;-----
	
      'CMS': begin  
        return,self.readdata_CMS()
      end
      
      'SUI': begin
      
        return,self.readdata_SUI()
      
      end
      
      
  ;------------------------------------------------------------
	
  'UKM':BEGIN
     
      return,self.readdata_UKM()
  END 

  ;---------------------------------------------------------------------------	
  ; H. Joachim Lutz CREW2 data (eummef)
  ; --------------------------------------------------------------------------	

  'EUM':BEGIN

    return,self.readdata_EUM()
  END ; END case block EUM
	
  ;--------------------------------------------------------------

  'OCA': BEGIN 	
      return, self.readdata_OCA()    
    END
    
  'CLV': begin
  
      return, self.readdata_CLV()
  
  end  
  
    'LARN': begin
  
      return, self.readdata_LARN()
  
  end
  
		
  'MPF': BEGIN

    if keyword_set(uncertainty) then error_message_uncertainty, self.grp	

    CASE self.product of
      'cmb': self.Infile = FILE_SEARCH(self->build_source_path(),self->get_date(/string) $
                            +'_EUMETSAT_MPEF_CFR.gz',c=c)		
      'ctp': self.Infile = FILE_SEARCH(self->build_source_path(),self->get_date(/string) $
                            +'_EUMETSAT_MPEF_CTP.gz',c=c)
      'ctt': self.Infile = FILE_SEARCH(self->build_source_path(),self->get_date(/string) $
                            +'_EUMETSAT_MPEF_CTT.gz',c=c)
      'cph': self.Infile = FILE_SEARCH(self->build_source_path(),self->get_date(/string) $
       	                    +'_EUMETSAT_MPEF_CPH.gz',c=c)
      ELSE: BEGIN
        print, '*** Error in cws_read__readdata.pro: for group '+self.grp+' parameter '+self.product+' is not available!'
        self->print_log, '*** Error in cws_read__readdata.pro: for group '+self.grp+' parameter '+self.product+' is not available!'
        RETURN,-1
      END
    ENDCASE

    IF c eq 0 THEN RETURN,-1
    spawn, 'gunzip -cf '+self.Infile[0] +' > /tmp/loesch.bin'

    CASE self.product of
      'cmb': data = read_binary('/tmp/loesch.bin',data_dims=[3712,3712],data_type=1)
      'ctp': data = read_binary('/tmp/loesch.bin',data_dims=[3712,3712],data_type=2)    		
      'ctt': data = read_binary('/tmp/loesch.bin',data_dims=[3712,3712],data_type=2)        				
      'cph': data = read_binary('/tmp/loesch.bin',data_dims=[3712,3712],data_type=1)
      ELSE: BEGIN 
        print, '*** Error in cws_read__readdata.pro: for group '+self.grp+' parameter '+self.product+' is not available!'
        self->print_log, '*** Error in cws_read__readdata.pro: for group '+self.grp+' parameter '+self.product+' is not available!'
        RETURN,-1
      END
    ENDCASE

    ;window,1
    ;view2d, data, /cool, /colo;, no_data_idx=where(data eq 0)

    if self.product eq 'cph' then begin 
        ;cmb = self->get_data(pr='cmb')
        ;self.product='cph' 
        ;data = 0.*(cmb eq 0) + 1.*(data eq 1 and (cmb gt 1.5)) $
        ;                      + 2.*(data eq 2 and (cmb gt 1.5)) $
        ;                      + 3.*(data eq 3 and (cmb gt 1.5)) $
        ;                      + 4.*(cmb eq 1)
      data =    -1.*(data eq 0.) $ ; no data
             +   0.*(data eq 1.) $ ; water cloud
             +  50.*(data eq 3.) $ ; unsure
             + 100.*(data eq 2.)   ; ice cloud

    endif 

    ;window, 2
    ;view2d, data, /cool, /colo, no_data_idx=where(data eq -1.)
    RETURN, data
	
  END ; case block MPF
	
  ;----------------------------------------------------------------------------------------

  'FUB':BEGIN
 
    if keyword_set(uncertainty) then error_message_uncertainty, self.grp	

    fobj = obj_new('msg_data_cl')
    fobj.set_date,self.year, self.month, self.day, self.hour, self.minute			
    data = fobj->get_product(strmid(self.product,0,2) eq 'cm' ? 'cm' : self.product)
    obj_destroy,fobj
 
    CASE self.product OF
	 
      'cmb':BEGIN
        
		IF size(data,/n_dim) ne 2 THEN RETURN, -1
        
		img = 0.* (data LT 0) +$
              1.* (between(data,0,50)) + $
              2.* (data GT 50) 
        			
        RETURN,img
      END
        
      'cm1':BEGIN
        	
        IF size(data,/n_dim) ne 2 THEN RETURN, -1
        img = 0.* (data lt 0) +$
              1.* (between(data,0,95)) + $
              2.* (data gt 95) 
        			
        RETURN,img
      END
        
      'cm2':BEGIN
        	
        IF size(data,/n_dim) ne 2 THEN RETURN, -1
        img = 0.* (data lt 0) +$
        	  1.* (between(data,0,5)) + $
        	  2.*	(data gt 5) 
        			
        RETURN,img
      END
   
      'ctp':BEGIN
   
        IF size(data,/n_dim) ne 2 THEN RETURN,-1
        cmaske = self->get_data(product='cmb',group='FUB')
        self->set_product,'ctp'
   
        nodata_idx = where(cmaske lt 1.5,nodata_anz)
        img = data
        IF nodata_anz gt 0 THEN img[nodata_idx]=-1.
         	
        RETURN,img
      END
 
      ELSE: BEGIN 
        print, '*** Error in cws_read__readdata.pro: for group '+self.grp+' parameter '+self.product+' is not available!'
        self->print_log, '*** Error in cws_read__readdata.pro: for group '+self.grp+' parameter '+self.product+' is not available!'
        RETURN,-1
      END
 
    ENDCASE
  END
  ;-------------------------------------------------------------------------------------------------------------
  ;  Deutsche Luft und Raumfahrt
  ; 	
  'DLR':BEGIN

        img = self.readdata_dlr()
        
      END
    
      ELSE: BEGIN 
        print, '*** Error in cws_read__readdata.pro: for group '+self.grp+' parameter '+self.product+' is not available!'
        self->print_log, '*** Error in cws_read__readdata.pro: for group '+self.grp+' parameter '+self.product+' is not available!'
        RETURN,-1
      END
      
    ENDCASE	
	
  END

  ;------------------------------------------------------------
	
  'COX':BEGIN
    
    if keyword_set(uncertainty) then error_message_uncertainty, self.grp	

    CASE self.product of
      
      'cmb': BEGIN
        file_ic = file_search(self->build_source_path()+self->get_date(/string)+'_MSG2_HRIT_TAU___IC_COCS.dat',c=c)
        IF c eq 0 THEN BEGIN 
          IF verbose THEN BEGIN 
            PRINT, '... Error in cws_read__readdata'
            PRINT, '    can not read ', self->build_source_path()+self->get_date(/string)+'_MSG2_HRIT_TAU___IC_COCS.dat'
          ENDIF 
          RETURN, -1
        ENDIF ELSE IF verbose THEN PRINT, '... read ', file_ic
        data = read_binary(file_ic, data_dims=[3712,3712], data_type=4)
        cod  = rotate(data,5)

        ;window,1
        ;view2d, cod, /cool, /colo ;, no_data_idx=where(data eq 0)
        ;histo = histogram(cod, LOCATIONS=loc)
        ;for i = 0, n_elements(histo)-1 do print, loc[i], histo[i] 
        img = 0.*(cod eq -1.) + 1.*(cod ne -1.) + 1.*(cod gt 0)
        ;window,2
        ;view2d, img, /cool, /colo ;, no_data_idx=where(data eq 0)
        RETURN, img
      END
      ELSE: BEGIN 
        print, '*** Error in cws_read__readdata.pro: for group '+self.grp+' parameter '+self.product+' is not available!'
        self->print_log, '*** Error in cws_read__readdata.pro: for group '+self.grp+' parameter '+self.product+' is not available!'
        RETURN,-1
      END


      'cth' : BEGIN
        self.infile = file_search(self->build_source_path()+self->get_date(/string)+'_MSG2_HRIT_CTZ___IC_COCS.dat',c=c)
        IF c eq 0 THEN BEGIN 
          IF verbose THEN BEGIN 
            PRINT, '... Error in cws_read__readdata'
            PRINT, '    can not read ', self->build_source_path()+self->get_date(/string)+'_MSG2_HRIT_CTZ___IC_COCS.dat'
          ENDIF 
          RETURN, -1
        ENDIF ELSE IF verbose THEN PRINT, '... read ', self.infile

        data = read_binary(self.infile, data_dims=[3712,3712], data_type=4)
        data = rotate(temporary(data),5)
  
        RETURN, data
      end

      'cod': BEGIN
        file_ic = file_search(self->build_source_path()+self->get_date(/string)+'_MSG2_HRIT_TAU___IC_COCS.dat',c=c)
        IF c eq 0 THEN BEGIN 
          IF verbose THEN BEGIN 
            PRINT, '... Error in cws_read__readdata'
            PRINT, '    can not read ', self->build_source_path()+self->get_date(/string)+'_MSG2_HRIT_TAU___IC_COCS.dat'
          ENDIF 
          RETURN, -1
        ENDIF ELSE IF verbose THEN PRINT, '... read ', file_ic
        data = read_binary(file_ic, data_dims=[3712,3712], data_type=4)
        img  = rotate(data,5)
      
        ;window,1
        ;view2d, img, /cool, /colo ;, no_data_idx=where(data eq 0)
        histo = histogram(img, LOCATIONS=loc)
        for i = 0, n_elements(histo)-1 do print, loc[i], histo[i] 

        ;cmb = self->get_data(product='cmb', group='DLR')
        ;self.product = 'cod'
        ;self.grp = 'COX'
        ;nodata_idx = where(cmb lt 1.5, nodata_anz)
        ;IF nodata_anz gt 0 THEN img[nodata_idx]=-1.
        RETURN, img
      END
      ELSE: BEGIN 
        print, '*** Error in cws_read__readdata.pro: for group '+self.grp+' parameter '+self.product+' is not available!'
        self->print_log, '*** Error in cws_read__readdata.pro: for group '+self.grp+' parameter '+self.product+' is not available!'
        RETURN,-1
      END


    ENDCASE	
  END


   ;-------------------------------------------------------------------------------------------------------	
   ; Alessandro.Ipe@oma.be	
  'RMB' :BEGIN

    if keyword_set(uncertainty) then error_message_uncertainty, self.grp

    CASE self.product of
      'cmb': self.infile = FILE_SEARCH(self->build_source_path()+'*CM_' +self->get_date(/string)+'00.hdf',c=c)
      'cod': self.infile = FILE_SEARCH(self->build_source_path()+'*COT_'+self->get_date(/string)+'00.hdf',c=c)  
      'cph': self.infile = FILE_SEARCH(self->build_source_path()+'*CPH_'+self->get_date(/string)+'00.hdf',c=c)	  
      ELSE:BEGIN 
        print, '*** Error in cws_read__readdata.pro: for group '+self.grp+' parameter '+self.product+' is not available!'
        self->print_log, '*** Error in cws_read__readdata.pro: for group '+self.grp+' parameter '+self.product+' is not available!'
        RETURN,-1
      END 
    ENDCASE

    IF c eq 0 THEN BEGIN 
      if verbose then print, '*** Warning '
      if verbose then print, '    '+self->build_source_path()+'*'+self.product+'_' +self->get_date(/string)+'00.hdf'
      if verbose then print, '    not available!!!'
      RETURN, -1
    ENDIF 
    if verbose then print, '... read data from '+self.infile
    fileId = h5f_open(self.infile)	

    CASE self.product of
      'cmb': dataId = h5d_open(fileID,'Cloud_mask')
      'cod': dataId = h5d_open(fileID,'Cloud_optical_thickness')  
      'cph': dataId = h5d_open(fileID,'Cloud_phase')	  
      ELSE:BEGIN 
        print, '*** Error in cws_read__readdata.pro: for group '+self.grp+' parameter '+self.product+' is not available!'
        self->print_log, '*** Error in cws_read__readdata.pro: for group '+self.grp+' parameter '+self.product+' is not available!'
        RETURN,-1
      END 
    ENDCASE

    data = h5d_read(dataID) 
    H5D_CLOSE, dataID
    H5F_CLOSE, fileID
    data = rotate(temporary(data),7)

    ;window, 1
    ;view2d, data, /cool, /colo, no_data_idx=where(data eq 255)
    histo = histogram(data, LOCATIONS=loc)
    for i = 0, n_elements(histo)-1 do print, loc[i], histo[i] 

    CASE self.product of
      'cmb': BEGIN 
         ;    0   undefined                            = no retrieval possible
         ;    1   uncontrasted                         = no retrieval possible
         ;    2   shadowed                             = no retrieval possible
         ;    3   clear                                = retrieval successful
         ;    4   cloudy or dust (misidentification)   = retrieval successful
         ;  255   deep-space                           = no retrieval possible
         data = (data eq 3.) + 2.* (data eq 4)
      END 
      'cod': BEGIN
	cmaske = self->get_data(product='cmb',group='RMB')
	self->set_product,'cod'
	nodata_idx = where(cmaske lt 1.5 or data le 0, nodata_anz)
	IF nodata_anz gt 0 THEN data[nodata_idx]=-1.
      END
      'cph':BEGIN
         ;    0   water (or no clouds!)
         ;    1   ice or dust (misidentification) 
         ;  255   undefined (only deep space)
        cmb = self->get_data(product='cmb',group='RMB')
        self->set_product,'cph'
	cmb = round(cmb)		
	;data = 0.*(cmb eq 0) + 1.*(data eq 0) + 2.*(data eq 1) + 4.*(cmb eq 1)
        data = -1.*(cmb eq 0 or cmb eq 1) + 0.*(data eq 0 and cmb eq 2) + 100.*(data eq 1 and cmb eq 2)
      END  
      ELSE: BEGIN
        print, '*** Error in cws_read__readdata.pro: for group '+self.grp+' parameter '+self.product+' is not available!'
        self->print_log, '*** Error in cws_read__readdata.pro: for group '+self.grp+' parameter '+self.product+' is not available!'
        RETURN,-1
      END
    ENDCASE

    ;window, 2
    ;view2d, data, /cool, /colo, no_data_idx=where(data eq -1)

    RETURN, data
  END

;-------------------------------------------------------------------------------------------------------
;  Algorithm Working Group of NOAA, CIMSS Madison
;-------------------------------------------------------------------------------------------------------

  'AWG':BEGIN
 	
    if keyword_set(uncertainty) then error_message_uncertainty, self.grp		
	
    self.inFile = file_search(self->build_source_path(), $
 		'geocatL2.Meteosat-9.'+self->get_date(/string,/year,/day_of_year) $
 		 +'.'+self->get_date(/string,/hour,/minute)+'*0.hdf*' ,c  = c)
 			
    IF c EQ 0 THEN RETURN , -1
      print,(file_info(self.infile)).size
      IF (FILE_INFO(self.infile)).size LT 3000 THEN BEGIN
        PRINT,'FILE existing, but too small ; something wrong '+self.infile
        RETURN,-1
      ENDIF		
      catch,error
      if error NE '' then begin
      print,'*** Error in cws_read__readdata: something wrong again'+self.infile
      return,-1	
    endif
   
    CASE self.product OF
 		
      'cmb': BEGIN		
        cmb = read_hdf_ssec(self.infile,'baseline_cmask_seviri_cloud_mask',lat = lat)
        img = (lat gt -90 ) + (lat gt -90 and (cmb eq 0 or cmb eq 1)  )
        img = ROTATE(reform(img,3712,3712),7)
 
        ; correct for vza larger than 69 degrees 
        ncdf_get_field, '/usr/people/hamann/TOOLS/cws3/trunk/MSG_data/MSG_seviri_geometry.nc', 'vza', vza, missing_value=mv
        img[where(vza ge 69)] = -1
	
        RETURN,img
      END
 			
      'ref':BEGIN
        ref = read_hdf_ssec(self.infile,'DCOMP_mode_1_cloud_particle_effective_radius')	
	refu =  read_hdf_ssec(self.infile,'DCOMP_mode_1_cloud_particle_effective_radius_error')	
	nodata_idx=where(ref le 0 or refu gt 1.,nodata_anz)
 	img = float(ref)
 	IF nodata_anz gt 0 THEN img[nodata_idx]=-1.
 			
        RETURN,img 					
      END
 			
      'cod':BEGIN
        cod = read_hdf_ssec(self.infile,'DCOMP_mode_1_cloud_optical_depth_vis')
        codu = read_hdf_ssec(self.infile,'DCOMP_mode_1_cloud_optical_depth_vis_error')
        nodata_idx=where(cod le 0 or codu gt 1. ,nodata_anz)
        IF nodata_anz gt 0 THEN cod[nodata_idx]=-1.
        RETURN,cod
      END
 			
      'ctp':BEGIN
        ctp = read_hdf_ssec(self.infile,'ACHA_mode_3_cloud_top_pressure',lat = lat)
		ctp = rotate(ctp,7)
 		cmb = self.get_data(group='AWG',product='cmb')
 		self.set_product,'ctp'
 		nodata_idx=where((ctp le 0) OR between(cmb,0.5,1.5),nodata_anz)
        IF nodata_anz gt 0 THEN ctp[nodata_idx]=-1.
        RETURN,ctp
      END
 					
      'ctt' : BEGIN
        ctt = read_hdf_ssec(self.infile,'ACHA_mode_3_cloud_top_temperature')
 		ctt = rotate(ctt,7)
 		cmb = self->get_data(group='AWG',product='cmb')
        self.set_product,'ctt'
 	    nodata_idx=where((ctt le 180) OR between(cmb,0.5,1.5),nodata_anz)
        IF nodata_anz gt 0 THEN ctt[nodata_idx]=-1.
        RETURN,ctt
      END
 				
      'cth':BEGIN
        raw = read_hdf_ssec(self.infile,'ACHA_mode_3_cloud_top_height')
        cth = rotate(raw,7)
        cmb = self.get_data(group='AWG',product='cmb')
        self.set_product,'cth'
 	cth /=1000.  ; m -> km	
        nodata_idx=where((cth le 0) OR between(cmb,0.5,1.5),nodata_anz)
        IF nodata_anz gt 0 THEN cth[nodata_idx]=-1.
 	RETURN,cth
      END
 			
      'cph':BEGIN
        cph = read_hdf_ssec(self.infile,'baseline_ctype_seviri_cloud_phase',lon=lon)
        cph = round(rotate(cph,7))
        ; data  =   0.* (cph gt  4) + 1.* (between(cph,1,3)) + 2.* (cph eq 4) $
        ;         + 4.* (cph eq 0)
                
        data =   0.* (cph eq 5) + 1.*(cph eq 1) + 2.*(cph eq 4) $
               + 3.*((cph eq 3) or (cph eq 2)) + 4.*(cph eq 0)
 	RETURN, data
      END
 			
      'lwp':BEGIN
        cod = self.get_data(group='AWG',product='cod')	
	ref = self.get_data(group='AWG',product='ref')
		
	IF n_elements(cod) eq 1 or n_elements(ref) eq 1 THEN return,-1
	
        lwp = cod * ref *5./9.
        cph = self.get_data(group='AWG',product='cph')
        self.set_product,'lwp'
        iwp = (cod^(1D/0.84))/0.065
        img = lwp * (cph eq 1) + iwp * (cph eq 2) + (-1.) * (cph ne 1 and cph ne 2)
	RETURN, img
      END
	
      ELSE: BEGIN 
        print, '*** Error in cws_read__readdata.pro: for group '+self.grp+' parameter '+self.product+' is not available!'
        self->print_log, '*** Error in cws_read__readdata.pro: for group '+self.grp+' parameter '+self.product+' is not available!'
        RETURN,-1
      END 
    ENDCASE
  END
		  
  ;-------------------------------------------------------------------------------------
	
  'GSF': BEGIN

    if keyword_set(uncertainty) then error_message_uncertainty, self.grp

    ;  Cloud_Top_Temperature
    ;  Cloud_Optical_Thickness
    ;  Cloud_Effective_Radius_16
    ;  Cloud_Water_Path
    ;  Cloud_Phase_Optical_Properties
    ;  Above_Cloud_Water_Vapor	

    ; create file name and find file
    self.infile = FILE_SEARCH(self->build_source_path() $
                   +self->get_date(/string,/year,/month,/day_single)+'.' $
                   +self->get_date(/string,/hour,/minute)+ '.OD.hdf*',c=c)

    if not quiet then print, '*** read file ', self.infile

    ; if only ziped file exist, then unzip it
    IF strmid(self.infile,3,3,/re) eq '.gz' THEN BEGIN
      spawn,'gunzip '+self.infile
      self.infile = FILE_SEARCH(self->build_source_path() $
                       +self->get_date(/string,/year,/month,/day_single)+'.' $
                       +self->get_date(/string,/hour,/minute)+ '.OD.hdf',c=c)
    ENDIF

    ; return if no file exists
    IF c eq 0 THEN BEGIN 
      print, '*** Warning in cws_read__readdata: can not find file:'
      print, '    '+self->build_source_path() $
                       +self->get_date(/string,/year,/month,/day_single)+'.' $
                       +self->get_date(/string,/hour,/minute)+ '.OD.hdf'
      RETURN, -1
    ENDIF 

    CASE self.product of
     'cmb': BEGIN
	  
	sds_read,self.InFile,ctp,sds='Cloud_Top_Pressure',/read_all
		
	;	IF n_elements(cmb) le 3712 THEN BEGIN		 
	;	  cd,file_dirname(self.infile),current= current
	;	  spawn,'./add_cm2.out '+ file_basename(self.infile)
	;	  sds_read,self.InFile,cmb,sds='CloudMask_2',/read_all
	;	  cd, current
	;	ENDIF
		 
	sds_read,self.infile,latitude,sds='MSG_Latitude',/Read_all
	data =  (ctp eq 0 AND latitude gt -500) + 2.* ( ctp gt 0 AND (latitude gt -500))  
	data = rotate(data,7)

        ; correct for vza larger than 69 degrees 
        ncdf_get_field, '/usr/people/hamann/TOOLS/cws3/trunk/MSG_data/MSG_seviri_geometry.nc', 'vza', vza, missing_value=mv
        ;view2d, vza, /cool, /colo, no_data_idx=where(vza eq mv)
        vza_limit = 79.5
        img =    0.*(vza gt vza_limit or vza eq mv) + 1.*(vza le vza_limit) + 1.*(data eq 2) 
                  ; outside retrieval or disc           ; measurement         ; 1+1=2 for cloud    
        img[where(vza ge vza_limit)] = 0

	RETURN,img					
		
      END
		  
      'ctp': BEGIN
		  
	 sds_read, self.InFile, data, sds='Cloud_Top_Pressure', scale=scale, offset=offset, /read_all
         ;view2d, data, /cool, /colo, /asp, /full_screen;, no_data_idx=where(vza eq mv)
  
         data = scale[0]*(data - offset[0])

	 nodata_idx = where(data le 0 ,nodata_anz)   ; old version was where(data lt 0 ,nodata_anz)
	       
	 IF nodata_anz gt 0 THEN data[nodata_idx]=-10.  ; -10 * 0.1 see next line is error marker -1.
	 data = rotate(data,7)

         ;window, /free
         ;view2d, data, /cool, /colo, /asp, /full_screen

	 RETURN,data

      end  	
		
      'ctt': BEGIN
   
         sds_read,self.InFile,data, sds='Cloud_Top_Temperature', scale=scale, offset=offset, /read_all ;
         nodata_idx = where(data lt 0 ,nodata_anz) 
         data = scale[0]*(data - offset[0])

         IF nodata_anz gt 0 THEN data[nodata_idx]=-1.
         img = rotate(data,7)
         print,minmax(img)
        
         ;window, 1
         ;view2d, img, /cool, /colo, no_data_idx=where(img eq -1)
         ;histo = histogram(img, LOCATIONS=loc)
         ;for i = 0, n_elements(histo)-1 do print, loc[i], histo[i] 

         RETURN,img
 
      end  

      'cth': BEGIN

         sds_read,self.InFile,data,sds='Cloud_Top_Height', scale=scale, offset=offset, /read_all
         nodata_idx = where(data lt 0 ,nodata_anz)
         data = scale[0]*(data - offset[0])
         data /=1000.  ; m -> km
	
         IF nodata_anz gt 0 THEN data[nodata_idx]=-1.
         print,minmax(data)

         RETURN,rotate(data,7)
 
      end  

			
      'cod': BEGIN
         
        CASE strLowCase(version) OF
          'crew2': BEGIN 
            sds_read,self.InFile,data,sds='Cloud_Optical_Thickness', scale=scale, offset=offset, /read_all
          END 
          'crew3':BEGIN
            sds_read,self.InFile,data,sds='Cloud_Optical_Thickness_16', scale=scale, offset=offset,/read_all
          END  
          ELSE: BEGIN 
            print,           '*** Error in cws_read__readdata.pro: for group '+self.grp+' parameter '+self.product+' !'
            self->print_log, '*** Error in cws_read__readdata.pro: for group '+self.grp+' parameter '+self.product+'!'
            print,           '    Unknown data version: ', version
            self->print_log, '    Unknown data version: ', version
            RETURN,-1
          END
	ENDCASE    

        nodata_idx = where(data lt 0 ,nodata_anz)
        data = scale[0]*(data - offset[0])

        IF nodata_anz gt 0 THEN data[nodata_idx]=-1.
        data = rotate(data,7)
        RETURN,data

      end  
		
      'ref': BEGIN
  
        sds_read, self.InFile, data, sds='Cloud_Effective_Radius_16', scale=scale, offset=offset,/read_all
        nodata_idx = where(data lt 0 ,nodata_anz)
        data = scale[0]*(data - offset[0])

        IF nodata_anz gt 0 THEN data[nodata_idx]=-1.
        data = rotate(data,7)
 
        RETURN,data
      end  
		

		
		'ctt': BEGIN
		  self.infile = FILE_SEARCH(self->build_source_path() $
								+self->get_date(/string,/year,/month,/day_single)+'.' $
								+self->get_date(/string,/hour,/minute)+ '.OD.hdf*',c=c)
								
		  IF c eq 0 THEN RETURN,-1
		   
		  IF strmid(self.infile,3,3,/re) eq '.gz' THEN BEGIN
		     spawn,'gunzip '+self.infile
		     self.infile = FILE_SEARCH(self->build_source_path() $
								+self->get_date(/string,/year,/month,/day_single)+'.' $
								+self->get_date(/string,/hour,/minute)+ '.OD.hdf',c=c)
		  endIF
		  
		  sds_read,self.InFile,data,sds='Cloud_Top_Temperature',/read_all
		  
		  nodata_idx = where(data lt 0 ,nodata_anz)
		
		 IF nodata_anz gt 0 THEN data[nodata_idx]=-1.
		
		 print,minmax(data)
		  RETURN,rotate(data,7)
		
		end  
		
		
		'cod': BEGIN
		  self.infile = FILE_SEARCH(self->build_source_path() $
								+self->get_date(/string,/year,/month,/day_single)+'.' $
								+self->get_date(/string,/hour,/minute)+ '.OD.hdf*',c=c)
								
		  IF c eq 0 THEN RETURN, -1
		   
		  IF strmid(self.infile,3,3,/re) eq '.gz' THEN BEGIN
		     spawn,'gunzip '+self.infile
		     self.infile = FILE_SEARCH(self->build_source_path() $
								+self->get_date(/string,/year,/month,/day_single)+'.' $
								+self->get_date(/string,/hour,/minute)+ '.OD.hdf',c=c)
		  endIF
		  
		  sds_read,self.InFile,data,sds='Cloud_Optical_Thickness',/read_all
		  
		  nodata_idx = where(data lt 0 ,nodata_anz)
		  
		 IF nodata_anz gt 0 THEN data[nodata_idx]=-1.
		 data = rotate(data,7)
		
		  RETURN,data
		
		end  
		
		'ref': BEGIN
		  self.infile = FILE_SEARCH(self->build_source_path() $
								+self->get_date(/string,/year,/month,/day_single)+'.' $
								+self->get_date(/string,/hour,/minute)+ '.OD.hdf*',c=c)
								
		  IF c eq 0 THEN RETURN,-1
		   
		  IF strmid(self.infile,3,3,/re) eq '.gz' THEN BEGIN
		     spawn,'gunzip '+self.infile
		     self.infile = FILE_SEARCH(self->build_source_path() $
								+self->get_date(/string,/year,/month,/day_single)+'.' $
								+self->get_date(/string,/hour,/minute)+ '.OD.hdf',c=c)
		  endIF
		  
		  sds_read,self.InFile,data,sds='Cloud_Effective_Radius_16',/read_all
		  
		  nodata_idx = where(data lt 0 ,nodata_anz)
		
		 IF nodata_anz gt 0 THEN data[nodata_idx]=-1.
		 data = rotate(data,7)
		 
		
		  RETURN,data
		
		end  
		
	  'cph': BEGIN
	   self.infile = FILE_SEARCH(self->build_source_path() $
								+self->get_date(/string,/year,/month,/day_single)+'.' $
								+self->get_date(/string,/hour,/minute)+ '.OD.hdf*',c=c)

  

        sds_read, self.InFile, data, sds='Cloud_Phase_Optical_Properties',/read_all

        CASE strLowCase(version) OF
          'crew2': BEGIN 
	    img = -1.*(cmb eq 0) + 0.*( data eq 2 ) + 100.*( data ge 3 ) ;$
 	         ;-1.*( data eq 0 and round(cmb) eq 1  ) 
          END 
          'crew3':BEGIN
            ; 0 = no clouds, 1 = water clouds, 2 = ice clouds, 6 = unknown phase
	    img = -1.*(data eq 0) + 0.*( data eq 1 ) + 50.*( data ge 6 ) + 100.*( data ge 2 ) ;$
 	         ;-1.*( data eq 0 and round(cmb) eq 1  ) 
          END  
          ELSE: BEGIN 
            print,           '*** Error in cws_read__readdata.pro: for group '+self.grp+' parameter '+self.product+' !'
            self->print_log, '*** Error in cws_read__readdata.pro: for group '+self.grp+' parameter '+self.product+'!'
            print,           '    Unknown data version: ', version
            self->print_log, '    Unknown data version: ', version
            RETURN,-1
          END
	ENDCASE


        data = rotate(data,7)
	cmb = self->get_data(product='cmb')
	self->set_product,'cph'
	;img = 0.*(cmb eq 0) + 1.*( data eq 2 ) $
        ;      + 2.*( data ge 3 ) $
 	;      + 4.*( data eq 0 and round(cmb) eq 1  ) 
 
        CASE strLowCase(version) OF
          'crew2': BEGIN 
	    img = -1.*(cmb eq 0) + 0.*( data eq 2 ) + 100.*( data ge 3 ) ;$
 	         ;-1.*( data eq 0 and round(cmb) eq 1  ) 
          END 
          'crew3':BEGIN
            ; 0 = no clouds, 2 = water clouds, 3 = ice clouds, 4 = unknown phase
	    img = -1.*(data eq 0) + 0.*( data eq 2 ) + 50.*( data gt 3 ) + 100.*( data eq 3 ) ;$
 	         ;-1.*( data eq 0 and round(cmb) eq 1  ) 
            ;img = data
          END  
          ELSE: BEGIN 
            print,           '*** Error in cws_read__readdata.pro: for group '+self.grp+' parameter '+self.product+' !'
            self->print_log, '*** Error in cws_read__readdata.pro: for group '+self.grp+' parameter '+self.product+'!'
            print,           '    Unknown data version: ', version
            self->print_log, '    Unknown data version: ', version
            RETURN,-1
          END
	ENDCASE
 
        ;window, 1
        ;view2d, img, /cool, /colo, no_data_idx=where(img eq -1)
        ;histo = histogram(img, LOCATIONS=loc)
        ;for i = 0, n_elements(histo)-1 do print, loc[i], histo[i] 

        RETURN,img
  
      end


	  
      'lwp': BEGIN
  
        CASE strLowCase(version) OF
          'crew2': BEGIN 
            sds_read,self.InFile,data,sds='Cloud_Water_Path', scale=scale, offset=offset,/read_all
          END 
          'crew3':BEGIN
            sds_read,self.InFile,data,sds='Cloud_Water_Path_16', scale=scale, offset=offset,/read_all
          END  
          ELSE: BEGIN 
            print,           '*** Error in cws_read__readdata.pro: for group '+self.grp+' parameter '+self.product+' !'
            self->print_log, '*** Error in cws_read__readdata.pro: for group '+self.grp+' parameter '+self.product+'!'
            print,           '    Unknown data version: ', version
            self->print_log, '    Unknown data version: ', version
            RETURN,-1
          END
	ENDCASE
  
        nodata_idx = where(data lt 0 ,nodata_anz)
        data = scale[0]*(data - offset[0])

        IF nodata_anz gt 0 THEN data[nodata_idx]=-1.
        data = rotate(data,7)
        RETURN,data
      END  
	  
	  
      ELSE:BEGIN 
        print, '*** Error in cws_read__readdata.pro: for group '+self.grp+' parameter '+self.product+' is not available!'
        self->print_log, '*** Error in cws_read__readdata.pro: for group '+self.grp+' parameter '+self.product+' is not available!'
        RETURN,-1
      END
    ENDCASE
  END


  ;------------------------------------------------
	
  'LAR': BEGIN
      return,self.readdata_LAR()
  END

  ;------------------------------------------------	
  ; dataset outside CREW
  'LSA':BEGIN
   
    if keyword_set(uncertainty) then error_message_uncertainty, self.grp		

 
	CASE self.product of
	  'hts':BEGIN
          data = fltarr(3712,3712)
          region=['SAfr','NAfr','Euro']
      
          FOR j=0,2 do BEGIN
            self.Infile = FILE_SEARCH(self->build_source_path()+'*LST_' $
                              +region[j]+'*' + self->get_date(/string)+'.bz2',c=c)
          			
            IF c eq 0 THEN continue
          	
            spawn,'bunzip2 -c '+self.Infile +' > /tmp/loesch.h5',gut,err
            	
            IF size(err,/dim) gt 0 THEN BEGIN & print,'dataFile' & continue & endIF
            fileID	=	H5F_OPEN('/tmp/loesch.h5') 
            dataID	=	H5D_OPEN(fileID,'LST')
            lst	=	h5D_READ(dataID)
            scaleID =	h5a_open_name(dataID,'SCALING_FACTOR')
            scale 	=	h5a_read(scaleID)
            scaleID =	h5a_open_name(dataID,'OFFSET')
            offset 	=	h5a_read(scaleID)
            scaleID =	h5a_open_name(dataID,'MISSING_VALUE')
            noData 	=	h5a_read(scaleID)
            H5D_CLOSE,dataID
            H5F_CLOSE,fileID
      
            lst = offset+(lst/scale)
            noData_idx = where(lst eq nodata,c)
            lst +=  273.15
            IF c gt 0 THEN lst[nodata_idx]=-1.
             
            lonFile=FILE_SEARCH(self->build_source_path()+'*LON_' $
            	                 +region[j]+'*' + '.bz2',c=c)
            spawn,'bunzip2 -c '+lonFile +' > /tmp/loesch.h5',gut,err
            
            fileID	=	H5F_OPEN('/tmp/loesch.h5') 
            dataID	=	H5D_OPEN(fileID,'LON')
            lon	=	h5D_READ(dataID)
            scaleID =	h5a_open_name(dataID,'SCALING_FACTOR')
            scale 	=	h5a_read(scaleID)
            scaleID =	h5a_open_name(dataID,'OFFSET')
            offset 	=	h5a_read(scaleID)
            scaleID =	h5a_open_name(dataID,'MISSING_VALUE')
            noData 	=	h5a_read(scaleID)
            H5D_CLOSE,dataID
            H5F_CLOSE,fileID
            	
            lon = offset+(lon/scale)
            noData_idx = where(lon eq noData,c)
            IF c gt 0 THEN lon[nodata_idx]=-999.
            	
            	
            latFile=FILE_SEARCH(self->build_source_path()+'*LAT_' $
            			+region[j]+'*'	+'.bz2',c=c)
            spawn,'bunzip2 -c '+latFile +' > /tmp/loesch.h5',gut,err
            	
            fileID	=	H5F_OPEN('/tmp/loesch.h5') 
            dataID	=	H5D_OPEN(fileID,'LAT')
            lat	=	h5D_READ(dataID)
            scaleID =	h5a_open_name(dataID,'SCALING_FACTOR')
            scale 	=	h5a_read(scaleID)
            scaleID =	h5a_open_name(dataID,'OFFSET')
            offset 	=	h5a_read(scaleID)
            scaleID =	h5a_open_name(dataID,'MISSING_VALUE')
            noData 	=	h5a_read(scaleID)
            H5D_CLOSE,dataID
            H5F_CLOSE,fileID
            	
            lat = offset+(lat/scale)
            noData_idx = where(lat eq noData,c)
            IF c gt 0 THEN lat[nodata_idx]=-999.
           	
            goodIND = wHERE((between(lst,200,400)) AND (lat ne -999.) AND  (lon ne -999.)  ,c)
            IF c eq 0 THEN continue
            indMsg = geo_to_msg(lon[goodIND],lat[goodIND])
            data[indMSG.column,indMSG.line]=lst[goodIND]
            undefine,lon & undefine,lat & undefine,lst
          ENDFOR
        
          RETURN,data
        END
        ELSE: BEGIN 
          print, '*** Error in cws_read__readdata.pro: for group '+self.grp+' parameter '+self.product+' is not available!'
          self->print_log, '*** Error in cws_read__readdata.pro: for group '+self.grp+' parameter '+self.product+' is not available!'
          RETURN,-1
        END

      ENDCASE
	
    end

    ;----------------------------------------------------------------------------------------------------------------
	
    'AMS':BEGIN

      if keyword_set(uncertainty) then error_message_uncertainty, self.grp			

      CASE self.product of
        'hto':BEGIN
          catch,error
          IF error ne 0 THEN BEGIN & print,'parameter '+self.product +' not available!' & RETURN,-1 & endIF
          self.InFile = FILE_SEARCH(self->build_source_path()+strmid(self->get_date(/string),0,8)+'/' $
                        ,'AMSR_E_L2_Ocean_*'+self.str_hour+self.str_minute+'.hdf',c=c)
        		
          IF c eq 0 THEN BEGIN & print,'parameter '+self.product +' not available!' & RETURN,-1 & endIF
        	
          sds_read,self.InFile,wvp,sds='Med_res_vapor',/read_all
          wvp =FLOAT(wvp)/ 100.
          sds_read,self.InFile,lon,sds='Longitude',/read_all
          sds_read,self.InFile,lat,sds='Latitude',/read_all
        	
          sds_read,self.Infile,qual,sds='Ocean_products_quality_flag',/read_All
          sds_read,self.InFile,lwp,sds='High_res_cloud',/read_all
          lwp =FLOAT(lwp)/ 10000.
          goodIND = wHERE((qual[3,*,*] EQ 0) AND between(lon,-80,80)  ,c)
          IF c eq 0 THEN RETURN,-99
          ; noice = WHERE((a.qual[0,*,*] AND 8) EQ 0 AND (a.qual[0,*,*] AND 3)
          ;               LT  2 AND $
          ;               a.lwp GE -0.1 AND a.lwp le  0.35 and  (a.qual[2,*,*] $
          ;               AND 63) EQ 0)
          ; i = WHERE(lon LT 0.0)
          ; IF i[0] NE -1 THEN lon[i]=360.0+lon[i]
          indMsg = geo_to_msg(lon[goodIND],lat[goodIND])
          data = fltarr(3712,3712)-1.
          i = WHERE(wvp lt 0.0)
        		
          IF i[0] NE -1 THEN wvp[i] = -1.
          ; pixelsize of AMSR is 21 km
        		
          ; for t=0,5 do for h=0,5 do BEGIN	
          ;   data[indMSG.column-2+t,indMSG.line-2+h]=wvp[goodIND]
          ; endfor
        	
          data[indMSG.column,indMSG.line]=wvp[goodIND]
          catch,/cancel
        	
          RETURN,data
        	
        END
			
	'lwp':BEGIN
	  self.InFile = FILE_SEARCH(self->build_source_path()+strmid(self->get_date(/string),0,8)+'/' $
				,'AMSR_E_L2_Ocean_*'+self.str_hour+self.str_minute+'.hdf',c=c)
					
	  IF c eq 0 THEN BEGIN & self->print_log,'parameter '+self.product +' not available!' & RETURN,-1 & endIF
				
          catch,error
          IF error ne 0 THEN BEGIN & print,'irgendwas nicht ok mit '+self.infile & RETURN,-1 & endIF
	  sds_read,self.InFile,lwp,sds='High_res_cloud',/read_all
	  lwp =FLOAT(lwp)/ 10000.
	  sds_read,self.InFile,lon,sds='Longitude',/read_all
	  sds_read,self.InFile,lat,sds='Latitude',/read_all
			
	  sds_read,self.Infile,qual,sds='Ocean_products_quality_flag',/read_All
		
	  catch,/cancel		
	  goodIND = wHERE((qual[3,*,*] EQ 0) AND between(lon,-70,70) ,c)
	  IF c eq 0 THEN RETURN,-99
	  ; noice = WHERE((a.qual[0,*,*] AND 8) EQ 0 AND (a.qual[0,*,*] AND 3)
          ;							LT  2 AND $
          ;              			a.lwp GE -0.1 AND a.lwp le  0.35 and  (a.qual[2,*,*] $
          ;										AND 63) EQ 0)
          ; i = WHERE(lon LT 0.0)
          ; IF i[0] NE -1 THEN lon[i]=360.0+lon[i]
	  indMsg = geo_to_msg(lon[goodIND],lat[goodIND])
	  data = fltarr(3712,3712)-1.
			
	  i = WHERE(lwp lt 0.0)
					
	  IF i[0] NE -1 THEN lwp[i] = -1.
	  ; pixelsize of AMSR is 12 km
	  for t=0,5 do for h=0,3 do BEGIN	
	    data[indMSG.column-2+t,indMSG.line-2+h]=lwp[goodIND]
	  endfor
							
	  RETURN,data
			
	END
	ELSE: BEGIN 
          print, '*** Error in cws_read__readdata.pro: for group '+self.grp+' parameter '+self.product+' is not available!'
          self->print_log, '*** Error in cws_read__readdata.pro: for group '+self.grp+' parameter '+self.product+' is not available!'
          RETURN,-1
        END 
      endCASE	
    END	

    ;---------------------------------------------------------------------------
    ; data set outside CREW ( water vapor) 	
		
    'DWD':BEGIN	

      if keyword_set(uncertainty) then error_message_uncertainty, self.grp	
	
      CASE 1 of 
        total(self.product eq ['hbl','hhl','hml','hto','hts']): BEGIN		
          IF self.year eq 2004 and self.month eq 10 THEN BEGIN
            CASE self.product of
              'hbl': filenameDum='_IWV_LAY1'
              'hhl': filenameDum='_IWV_LAY3'
              'hml': filenameDum='_IWV_LAY2'
              'hto': filenameDum='_IWV_TOTAL'
              'hts': filenameDum='_T_SURFACE'
              ELSE: 
            ENDCASE
            self.InFile = FILE_SEARCH(self->build_source_path() $
                          +self.str_year+'/'+self.str_month+'/'+self.str_day $
                          +'/'+self->get_date(/string)+filenameDum+'.dat.bz2')
           				
            IF self.Infile eq '' THEN BEGIN
              print, strupCASE(self.product)+'in*'+self->get_date(/string)+filenameDum+'.dat.bz2 does not exist!'
              RETURN,-1.
            endIF
     
            spawn,'bunzip2 -c '+self.Infile+' >/tmp/loesch.dat'	
            data = fltarr(3712,3712)
            openr,10,'/tmp/loesch.dat'
            readu,10,data
            close,10
            img = rotate(data,7)					
          ENDIF ELSE BEGIN
            self.InFile = FILE_SEARCH(self->build_source_path() $
         	                 +self.str_year+'/'+self.str_month+'/'+self.str_day $
         			 +'/'+strupCASE(self.product)+'in*'+self->get_date(/string)+'*MA*.gz')
 
            IF self.Infile eq '' THEN BEGIN
              print,strupCASE(self.product)+'in*'+self->get_date(/string)+'*MA*.gz does not exist!'
              RETURN,-1.
            endIF
            spawn,'gunzip -c '+self.Infile+' >/tmp/loesch.dat'
            data = fltarr(3712,3712)
            openr,10,'/tmp/loesch.dat',/swap_endian
            readu,10,data
            close,10
            img = rotate(data,7)
          ENDELSE	
          RETURN,img
        END				
      ELSE:self->print_log,'parameter not available!'
    endCASE		
  END
			
    ;---------------------------------------------------------------------------	
    ; Joro
    'EUJ': BEGIN
      if keyword_set(uncertainty) then error_message_uncertainty, self.grp	

      CASE self.product of
        'cm':BEGIN
          self.Infile = FILE_SEARCH(self->build_source_path(),self->get_date(/string)+'*CM')
          data = read_binary(self.Infile[0],data_dims=[3712,3712],data_type=1)
          RETURN,data
        END
	'ctp':BEGIN
          self.Infile =FILE_SEARCH(self->build_source_path(),self->get_date(/string)+'*CTP')
          data = read_binary(self.Infile[0],data_dims=[3712,3712],data_type=2,endian='big')
				
          nodata_idx = where(data lt 0,nodata_anz)
          img = float(data * (data gt 100))
				
          IF nodata_anz gt 0 THEN img[nodata_idx]=-1. 
          RETURN,img
	END
				
	'ctt':BEGIN
          self.Infile =FILE_SEARCH(self->build_source_path(),self->get_date(/string)+'*CTT',count=c)
          IF c eq 0 THEN RETURN,make_array(3712,3712,/float,value=-1.)
          data = read_binary(self.Infile[0],data_dims=[3712,3712],data_type=2,endian='big')
				
          nodata_idx = where(data lt 100,nodata_anz)
          img = float(data * (data gt 100))
          IF nodata_anz gt 0 THEN img[nodata_idx]=-1.
          RETURN,img
	END
	ELSE: self->print_log,'parameter '+self.product+' not available!'
      endCASE
    end
	
    ;------------------------------------------------------------------------------------------	
    ;  Hier fehlen die quality values!!!
    ; Watts
    'EUW':BEGIN

      if keyword_set(uncertainty) then error_message_uncertainty, self.grp		

      templ=restore_var(self->build_source_path()+'readTemplate.sav')			
      CASE self.product of
        'cm':BEGIN
          ; Besonderheit: keine Messungen ueber 70Grad viewing and sun zenith
	  sunZenith= self->sun_zenith(/temporary)
			
          viewAn = self->elevation() 
          mask =  (sunZenith le 70) and (viewAn ge 20)
        			
          undefine,viewAn 
          undefine,sunZenith
        				
        				
          self.Infile = FILE_SEARCH(self->build_source_path(),'OCA_Fr*v1.1*'+self->get_date(/string)+'*')
          IF self.Infile[0] eq '' THEN RETURN,bytarr(3712,3712)
          spawn, 'gunzip -c '+self.Infile[0] +' > /tmp/loesch.bin'
        						
          img  = read_binary('/tmp/loesch.bin',template=templ)
          ; data = 0*(img.qual eq 0) + $
          ;        1*(img.qual and (img.data lt 0.5)) +$
          ;        2*(img.qual and (img.data ge 0.5))				
          data = 	mask *((img.data lt 0.5)  + 2*(img.data ge 0.5))
        					
          print,total(img.qual)
          RETURN,data
        END
        'ctp':BEGIN
          self.Infile = FILE_SEARCH(self->build_source_path(),'OCA_Pc*v1.1*'+self->get_date(/string)+'*')
          IF self.Infile[0] eq '' THEN RETURN,intarr(3712,3712)-1
          spawn, 'gunzip -c '+self.Infile[0] +' > /tmp/loesch.bin'

          data = read_binary('/tmp/loesch.bin',template=templ)
          nodata_idx = where(data.(2) le 0,nodata_anz)
          img = float(data.(2) * (data.(2) gt 0))
          IF nodata_anz gt 0 THEN img[nodata_idx]=-1.
        
          RETURN,img
        END
        'cod':BEGIN
          self.Infile = FILE_SEARCH(self->build_source_path(),'OCA_OD*v1.1*'+self->get_date(/string)+'*')
          IF self.Infile[0] eq '' THEN RETURN,intarr(3712,3712)-1
          spawn, 'gunzip -c '+self.Infile[0] +' > /tmp/loesch.bin'
            
          data = read_binary('/tmp/loesch.bin',template=templ)
          nodata_idx = where((data.(2) lt 0) or (data.(3) ne 0),nodata_anz)
          
          img = float(data.(2))
          undefine,data
          stop
          IF nodata_anz gt 0 THEN img[nodata_idx]=-1.
          goodIdx = where(img ge 0)
          img[goodIdx] = 10^img[goodIdx]
          RETURN,img
        END
        
        'cph': BEGIN
          self.Infile = FILE_SEARCH(self->build_source_path(),'OCA_Re*v1.1*'+self->get_date(/string)+'*')
          IF self.Infile[0] eq '' THEN RETURN,intarr(3712,3712)-1
          spawn, 'gunzip -c '+self.Infile[0] +' > /tmp/loesch.bin'
          
          
          data  			= read_binary('/tmp/loesch.bin',template=templ)
          spawn,'rm -f /tmp/loesch.bin'	
          img = float(data.(2) gt 0)
          img += data.(2) ge 100
          
          nodata_idx	 	= where((data.(2) le 0) or (data.(3) ne 0),nodata_anz)
          		
          IF nodata_anz gt 0 THEN img[nodata_idx]=-1.
          RETURN,img			
        END
        				
        'cfr':BEGIN
          self.Infile = FILE_SEARCH(self->build_source_path(),'OCA_Fr*v1.1*'+self->get_date(/string)+'*')
          IF self.Infile[0] eq '' THEN RETURN,intarr(3712,3712)-1
          spawn, 'gunzip -c '+self.Infile[0] +' > /tmp/loesch.bin'
          
          
          data  = read_binary('/tmp/loesch.bin',template=templ)
          spawn,'rm -f /tmp/loesch.bin'	
          nodata_idx = where((data.(2) le 0) or (data.(3) ne 0),nodata_anz)
          img = 		100.*data.(2)				
          IF nodata_anz gt 0 THEN img[nodata_idx]=-1.
          RETURN,img
        END
        
        'ref':BEGIN
          self.Infile = FILE_SEARCH(self->build_source_path(),'OCA_Re*v1.1*'+self->get_date(/string)+'*')
          IF self.Infile[0] eq '' THEN RETURN,intarr(3712,3712)-1
          spawn, 'gunzip -c '+self.Infile[0] +' > /tmp/loesch.bin'
          
          
          data  = read_binary('/tmp/loesch.bin',template=templ)
          spawn,'rm -f /tmp/loesch.bin'	
          
          nodata_idx = where((data.(2) le 0) or (data.(3) ne 0),nodata_anz)
          img = 		data.(2)	mod 100			
          IF nodata_anz gt 0 THEN img[nodata_idx]=-1.
          RETURN,img
        END   
        ELSE: self->print_log,'parameter '+self.product+' not available!'
      endCASE
    END

    ; ------------------- 
    'KMR':BEGIN		

      if keyword_set(uncertainty) then error_message_uncertainty, self.grp 	

      self.Infile = FILE_SEARCH(self->build_source_path(),'meteosat*'+self->get_date(/string)+'*hdf',count=count)
      ;IF self.hour eq 12 THEN self.Infile = FILE_SEARCH(self->build_source_path(),'meteosat*'+'20060117_1200_000*.hdf',count=count)			
      ;self.Infile = FILE_SEARCH('/masp12/baltimos/SMHI/KMR_New/','meteosat*'+self->get_date(/string,/KMRstyle)+'*hdf',count=count)
			
      CASE self.product of
        'cm':BEGIN

          IF count eq 0 THEN RETURN, make_array(3712,3712,/byte,value=0B)
          fileID = h5f_open(self.Infile)
          datasetID = h5d_open(fileID,'cph')
          data	= h5d_read(datasetID)
          h5D_close, datasetID
          h5F_close, fileID
          data = rotate(data,7)
    
          img = 2.*((data eq 1) or (data eq 6))+$
                1.*(data eq 0) + $
                0.*(data eq 2)
    
          RETURN,img
        END
        			
        'ctt':BEGIN
          IF count eq 0 THEN RETURN, make_array(3712,3712,/float,value=-1.)
          fileID 		=	h5f_open(self.Infile)
          datasetID   =	h5d_open(fileID,'ctt')
          data		=	h5d_read(datasetID)
          h5D_close, datasetID
          h5F_close, fileID
          data = rotate(data,7)
          
          nodata_idx= where(data eq -1,nodata_anz)
          img = data/10.
          IF nodata_anz gt 0 THEN img[nodata_idx]=-1.
          RETURN,img
        END
       
        'cod':BEGIN
          IF count eq 0 THEN RETURN,make_array(3712,3712,/float,value=-1.)
          fileID = h5f_open(self.Infile)
          datasetID = h5d_open(fileID,'cot')
          data = h5d_read(datasetID)
          h5D_close, datasetID
          h5F_close, fileID
          data = rotate(data,7)
          nodata_idx= where(data eq -1,nodata_anz)
          img = data/100.
          IF nodata_anz gt 0 THEN img[nodata_idx]=-1.
          RETURN,img
        END
        				
        'lwp':BEGIN
          IF count eq 0 THEN RETURN,make_array(3712,3712,/float,value=-1.)
          fileID = h5f_open(self.Infile)
          datasetID = h5d_open(fileID,'lwp')
          data = h5d_read(datasetID)
          h5D_close, datasetID
          h5F_close, fileID
          data = rotate(data,7)
          nodata_idx= where(data eq -1,nodata_anz)
          img = data/5.
          IF nodata_anz gt 0 THEN img[nodata_idx]=-1.
          RETURN,img
        END
      
        'ref':BEGIN
          IF count eq 0 THEN RETURN,make_array(3712,3712,/float,value=-1.)
          fileID = h5f_open(self.Infile)
          datasetID = h5d_open(fileID,'reff')
          data = h5d_read(datasetID)
          datasetIDCPH = h5d_open(fileID,'cph')
          cph = h5d_read(datasetIDCPH)
          h5D_close, datasetIDCPH
          h5D_close, datasetID
          h5F_close, fileID
          data = rotate(data,7)
          cph  = rotate(cph,7)
          nodata_idx= where((cph ne 1) and (cph ne 6),nodata_anz)

          img = (data/10.)-20.*(cph eq 1)
          IF nodata_anz gt 0 THEN img[nodata_idx]=-1.
          RETURN,img
        END
        				
        'cph':BEGIN
      	
          IF count eq 0 THEN RETURN,make_array(3712,3712,/byte,value=0B)
          fileID 		=	h5f_open(self.Infile)
          datasetID   =	h5d_open(fileID,'cph')
          data		=	h5d_read(datasetID)
          h5D_close, datasetID
          h5F_close, fileID
          data = rotate(data,7)
        
          img = 2.*(data eq 1)+$
                1.*(data eq 6) + $
                3.*(data eq 2) + $
                0.*(data eq 0)
        	
          RETURN,img
        END							
        ELSE:	
      endCASE
    end
    	
    ;---------------------------------------------------------------------------------------		
    'KMV':BEGIN

      if keyword_set(uncertainty) then error_message_uncertainty, self.grp 	

      CASE self.product of
        'cm':BEGIN
 	 
          self.Infile = FILE_SEARCH(self->build_source_path(),'*EUROPECLOUDMASK_*' $
                        + string(self.year, self.month, self.day, self.hour, self.minute, $
                        format = '(i4.4,"' + '_' + '",3(i2.2,"' + '_' + '"),2i2.2,"' + '_' + '")')+'*')
          fileID 	 =   h5f_open(self.Infile)
          datasetID   =   h5d_open(fileID,'image1/image_data')
          data		 =   h5d_read(datasetID)
          h5D_close,datasetID
          h5F_close,fileID

          qualFile=FILE_SEARCH(self->build_source_path(),'*EUROPEMASKQUALITY*' $
                          + string(self.year, self.month, self.day, self.hour, self.minute, $
             				format = '(i4.4,"' + '_' + '",3(i2.2,"' + '_' + '"),2i2.2,"' + '_' + '")')+'*')
          fileID 	 =   h5f_open(qualFile[0])
          datasetID   =   h5d_open(fileID,'image1/image_data')
          quality	 =   h5d_read(datasetID)
          h5D_close,datasetID
          h5F_close,fileID
          dumSmall = data*0.
          dumSmall = 1 + ((data ne 0) and ((data AND 1B) ne 1B))

          img = bytarr(3712,3712)
          img[855:2854,2655:3654]= rotate(dumSmall,7)

          RETURN,img	 
        END
      
	'ctt': BEGIN
 	  self.Infile = FILE_SEARCH(self->build_source_path(), $
 	                       '*EUROPECLOUDTOPTEMPERATURE_*' $
 	                       +string(self.year, self.month, self.day, self.hour, self.minute, $
 	                       format = '(i4.4,"' + '_' + '",3(i2.2,"' + '_' + '"),2i2.2,"' + '_' + '")')+'*',$
 	                       count =c)
 	  IF c eq 0 THEN RETURN,make_array(3712,3712,/float,value=-1.)
 	  fileID = h5f_open(self.Infile)
 	  datasetID = h5d_open(fileID,'image1/image_data')
 	  data = h5d_read(datasetID)
 	  h5D_close,datasetID
 	  h5F_close,fileID
 	  img = fltarr(3712,3712)
 	  img[855:2854,2655:3654]= rotate(float(data)/100.,7)
 	  nodata_idx=where(img lt 200,nodata_anz)
 	  IF nodata_anz gt 0 THEN img[nodata_idx]=-1.
          RETURN,img
        END  
        ELSE:   
      ENDCASE			
    END
		
    ;-------------------------------------------------------------------------------------------------------		
    ; 
    'MFR':BEGIN
  
      if keyword_set(uncertainty) then error_message_uncertainty, self.grp 	

      ; create input file name
      CASE self.product OF
        'cmb': self.InFile = FILE_SEARCH(self->build_source_path(),'SAFNWC_MSG2_CMa*'  +self->get_date(/string)+'*.h5',c=cFile)
        'cm1': self.InFile = FILE_SEARCH(self->build_source_path(),'CMa*'              +self->get_date(/string)+'*hdf',c=cFile)
        'cm2': self.InFile = FILE_SEARCH(self->build_source_path(),'CMa*'              +self->get_date(/string)+'*hdf',c=cFile)
        'ctp': self.InFile = FILE_SEARCH(self->build_source_path(),'SAFNWC_MSG2_CTTH*' +self->get_date(/string)+'*h5' ,c=cFile)
        'ctt': self.InFile = FILE_SEARCH(self->build_source_path(),'SAFNWC_MSG2_CTTH_*'+self->get_date(/string)+'*h5' ,c=cFile) 
        'cth': self.InFile = FILE_SEARCH(self->build_source_path(),'SAFNWC_MSG2_CTTH_*'+self->get_date(/string)+'*h5' ,c=cFile)
        'cph': self.InFile = FILE_SEARCH(self->build_source_path(),'SAFNWC_MSG2_CT_*'  +self->get_date(/string)+'*h5' ,c=cFile)
        ; cws_read__define.pro:function cws_read::build_source_path
        ELSE: BEGIN 
          self->print_log,'*** Warning: parameter '+self.product+' not available for group '+self.grp+'!'
          print,          '*** Warning: parameter '+self.product+' not available for group '+self.grp+'!'
          END
      ENDCASE
  
      IF cFile EQ 0 THEN BEGIN 
        print, '*** ERROR in cws_read__readata: data file not found ', self.InFile
        RETURN, -1
      ENDIF
   
      IF NOT quiet THEN PRINT, '... read data from ', self.InFile, ' (cws_read__readdata.pro)'	
  
      ; read the data
      fileID = h5f_open(self.Infile)
  
      CASE self.product OF
        'cmb': datasetID = h5d_open(fileID,'CMa')
        'cm1': datasetID = h5d_open(fileID,'CMa')
        'cm2': datasetID = h5d_open(fileID,'CMa') 		 
        'ctp': datasetID = h5d_open(fileID,'CTTH_PRESS')
        'ctt': datasetID = h5d_open(fileID,'CTTH_TEMPER')
        'cth': datasetID = h5d_open(fileID,'CTTH_HEIGHT')
        'cph': datasetID = h5d_open(fileID,'CT_PHASE')				
        ELSE: print, '*** Warning: parameter '+self.product+' not available for group '+self.grp+'!'
      ENDCASE
  
      data = h5d_read(datasetID)
      h5D_close,datasetID
      h5F_close,fileID
  
      data = rotate(data,7)
      ;print, 'MFR raw data: ', min(data), max(data)
      ;window,1
      ;view2d, data, /cool, /colo ;, no_data_idx=where(data eq 0)
      ;histo = histogram(data, LOCATIONS=loc)
      ;for i = 0, n_elements(histo)-1 do print, loc[i], histo[i] 
  
      ; transform data to common standard
      CASE self.product OF
        'cmb': img = (data ge 1) + ((data eq 2) or (data eq 3))
        'cm1': img = 1. *((data eq 4) or (between(data , 1,2))) + 2.*(data eq 3)
        'cm2': img = 1. * (data eq 1) +  2. *  (data gt 1)
        'ctp': img = (-1)>((25.*data)-250.)
        'ctt': BEGIN
               nodata_idx= where(data eq 0,c)
               img = data+150.
               IF c gt 0 THEN img[nodata_idx]=-1.
               END			
        'cth': BEGIN
               data = (data*200.)-2000.
               data /=1000.
               nodata_idx= where(data le 0,c)
               img = data
               IF c gt 0 THEN img[nodata_idx]=-1.
               END			
        'cph': BEGIN
               ; read cloud binary mask
               cmb = self->get_data(product='cmb',group='MFR')
               self.product = 'cph'
               cmb = round(cmb)
  
               ; this does not fit to the CREW-3 data set any more
        	     ;img = 0.*(cmb eq 0) + 1.*(between(data, 4.5, 8.1) and (cmb gt 1.5)) $ ; water clouds
               ;                    + 2.*(between(data,10.5,18.1) and (cmb gt 1.5)) $ ; ice   clouds
               ;                    + 3.*(between(data, 8.2,10.1) and (cmb gt 1.5)) $ ; mixed clouds
               ;                    + 4.*(cmb eq 1)                                   ; no cloud
  
               img = 0.*(cmb eq 0) +   0.*(between(data, 0.5, 1.5) and (cmb gt 1.5)) $   ; water clouds
                                   + 100.*(between(data, 1.5, 2.5) and (cmb gt 1.5)) $   ; ice   clouds
                                   +  50.*(between(data, 2.5, 3.5) and (cmb gt 1.5)) $   ; mixed clouds
                                   -   1.*(cmb eq 1)                                     ; no cloud
               ;window, 1
               ;view2d, cmb, /cool, /color, /no_axes, /asp, /full_screen
               END			
        ELSE:self->print_log,'parameter '+self.product+' not available!'
     ENDCASE
  
     ; return image to the calling routine
     RETURN, img
  
    END ;  case block MFR
    ; ------------------------------------------------------------------------------------		
    ELSE: BEGIN 
      print, '*** Error in cws_read__readdata.pro: group '+self.grp+' is unknown!'
      self->print_log, '*** Error in cws_read__readdata.pro: group '+self.grp+' is unknown!'
      RETURN,-1
    END
  ENDCASE
END

; --------------
; short error message for uncertainties, that are not implemented jet
pro error_message_uncertainty, group, nodata=nodata, product

  if not keyword_set(nodata) then begin 
    print, '*** Error in cws_read__readdata'
    print, '    Reading the uncertainty for group ', group
    print, '    is not jet implemented'
    stop
  endif else begin 
    print, '*** Warning in cws_read__readdata'
    print, '    Reading no uncertainty for ', product
    print, '    was provided by group ', group
    stop
  endelse 
end