EIT Software Listings

 

anal
obsolete
response
util

 

Previous Routine
Next Routine

 

Listing of $SSW/soho/eit/idl/anal/eit_catrd.pro

 


FUNCTION search_cat, indate, long=long, raw=raw, yester=yester, lz=lz, $
		      no_next=no_next, short=short, input_file=input_file, $
		      records=records, filename=filename, tai=tai, $
                       start_date=start_date,stop_date=stop_date,web=web, $
                       wave=wave,filter=filter,nx=nx,ny=ny,xbin=xbin,$
                       ybin=ybin, object=object, cat_struct=cat_struct,$
                       ss=ss, sci_obj=sci_obj,infov=infov, uncommon=uncommon,$
                       high_c=high_c, nocals=nocals

common lz_struct,entry,lz_rec,lz_urec,lz_nrec

  IF n_elements(yester) EQ 0 THEN yester = 0
  IF keyword_set(lz) THEN lz=1 ELSE lz=0

; sci_obj not in QUICKLOOK DATA
  IF NOT lz then sci_obj = 0

  IF not(keyword_set(raw)) THEN text = 1 ELSE text = 0
  IF keyword_set(short)    THEN short = 1 ELSE short = 0

  ; The keyword /LONG:  0 mean sort cat records an remove duplicates and
  ; display short format else raw order with all duplicates and print the
  ; values of every catalog element.

  IF keyword_set(long) THEN long = 1 ELSE long = 0

  IF not keyword_set(cat_struct) THEN BEGIN
  ; Find the desired catalog
    cur_dir_cnt = 0
  ;1997/10/27 einfalt IF !version.os EQ 'vms' THEN lz_cat='cat_dir:lz_catalog.cat' ELSE $
    if IS_GSFCVMS() eq 1 then lz_cat='cat_dir:lz_catalog.cat' $
;;       else lz_cat=concat_dir(getenv('EIT_LZ'),'lz_catalog.cat')
    else begin
          cat_dir = get_logenv('EIT_LZ_CAT')
          if cat_dir ne '' then lz_cat=concat_dir(cat_dir,'lz_catalog.cat') $
          else lz_cat=concat_dir(getenv('EIT_LZ'),'lz_catalog.cat')
    endelse
    IF n_elements(input_file) ne 0 THEN dir_list = input_file ELSE $
    IF lz THEN dir_list = lz_cat ELSE BEGIN
       dir_list = CAT_DIRECTORY( indate,  cur_dir_cnt  = cur_dir_cnt,   $
		                  use_last_rec = use_last_rec,  $
				  yester       = yester,	$
				  no_next      = no_next,	$
		                  dir_cnt      = dir_cnt)

      IF dir_cnt EQ 0 THEN BEGIN
	  !quiet = 0
	  return, 'No catalogs found in CAT_DIR:'   	; no catalogs
        ENDIF ELSE IF dir_list(0) EQ '' THEN BEGIN
	  !quiet = 0
	  return, ''
        ENDIF
     ENDELSE

; save LZ structure for future use
     IF lz and n_elements(entry) ne 0 and not keyword_set(uncommon) THEN BEGIN
          u_rec = lz_urec
          n_rec = lz_nrec
          records = lz_rec
     ENDIF ELSE BEGIN
  ; Return the contents of the selected catalog as a "raw data" structure.
          entry = CAT_OPEN(   file  = dir_list(cur_dir_cnt), $		; input
                      lz    = lz, $                              ; input
		     long  = long,	$			; input
		     lun   = cat_unit, 	$			; output
		     u_rec = u_rec,     $			; output
		     n_rec = n_rec,     $			; output
		     records = records)				; output
          lz_urec = u_rec
          lz_nrec = n_rec
          lz_rec = records
     ENDELSE
  ; RECORDS is a array containing the record numbers of the catalog file
  ;         in the order indicated by the /LONG keyword
  ; U_REC   is the number of records to be used/considered
  ; N_REC   number of total record in the cat (excluding header)

  ENDIF ELSE BEGIN
    entry=cat_struct
    n_rec=n_elements(entry)
    u_rec=n_rec
    records=lindgen(n_rec)+1
    select=lindgen(u_rec)
  ENDELSE

;
; moved date selection out of if-then-else loop
;
     IF keyword_set(start_date) THEN start_date=anytim2utc(start_date) $
          ELSE start_date=anytim2utc('15-dec-1995')
     IF keyword_set(stop_date) THEN stop_date=anytim2utc(stop_date) $
          ELSE stop_date=anytim2utc(strmid(!stime,0,11))
     IF lz or keyword_set(cat_struct) THEN BEGIN
        IF keyword_set(indate) THEN BEGIN
          IF strpos(strlowcase(indate(0)),"/ye") ge 0 THEN $
                indate   = doy2utc(utc2doy(anytim2utc(!stime))-1) $
          ELSE IF strpos(strlowcase(indate(0)),"ye=") ge 0 THEN BEGIN
                back = (str_sep(indate(0),"="))(1)
                indate   = doy2utc(utc2doy(anytim2utc(!stime))-back)
          ENDIF
          start_date=anytim2utc(indate)
          stop_date=start_date
        ENDIF ELSE BEGIN
          IF keyword_set(yester) then begin
              indate = doy2utc(utc2doy(anytim2utc(!stime))-yester)
              start_date=anytim2utc(indate)
              stop_date=start_date
          ENDIF
        ENDELSE
     ENDIF

     if tag_exist(entry,'obs_time') then obstime = $
          anytim2utc({mjd:entry(records-1).obs_time.mjd+49718, $
	   	   time:entry(records-1).obs_time.sec*1000L}) else $
          obstime = anytim2utc(eit_fxpar(entry(records-1),'date_obs'))
     obstime = utc2sec(obstime)
     if stop_date.time eq 0 then stop_date.time = 86399000
     select=where(obstime ge utc2sec(start_date) and obstime le $
            utc2sec(stop_date))
;    select=where(obstime.mjd ge start_date.mjd and obstime.mjd le $
;            stop_date.mjd)
     IF select(0) EQ -1 THEN BEGIN
        message,/info,'No Images matching selected DATES were found'
        return,''
     ENDIF

; IF lz THEN BEGIN
;
; ENDIF ELSE select=lindgen(u_rec)

     IF keyword_set(wave) THEN BEGIN
        wave_list=[171,195,284,304]
        IF wave lt 170 THEN wave=wave_list(wave-1)
;       sel=where(entry(records-1).wave+170 EQ wave)
;       sel=fix(sel/4)
;       sel=where(eit_fxpar(entry(records-1),'wavelnth') EQ wave)
;
; 1997 June 3 -JSN fix bug
        if not tag_exist(entry,'simple') then begin
          dum = eit_fxpar(entry(records-1),'wavelnth',cat_waves=cat_waves)
          sel = where(cat_waves EQ wave)/4
        endif else sel=where(eit_fxpar(entry(records-1),'wavelnth') EQ wave)
;
        sel_index=where_arr(select,sel,cnt)
        IF cnt ne 0 THEN select=select(sel_index) ELSE BEGIN
            message,/info,'No images matching selections -WAVE- were found'
            return,''
        ENDELSE
     ENDIF

     filt_str = ['AL+1', 'BLK EST',  'CLEAR', 'BLK WST', 'AL+2' ]
     IF keyword_set(filter) THEN BEGIN
;       filt_num=where(filt_str EQ strupcase(filter))
;       IF filt_num(0) EQ -1 and strlen(filter) EQ 1 THEN filt_num=fix(filter)
;       sel=where(entry(records-1).filter EQ filt_num(0))
        IF strlen(filter) EQ 1 THEN filter = filt_str(fix(filter)) else $
          filter=strupcase(filter)
        sel=where(strupcase(eit_fxpar(entry(records-1),'filter')) EQ filter)
        sel_index=where_arr(select,sel,cnt)
        IF cnt ne 0 THEN select=select(sel_index) ELSE BEGIN
            message,/info,'No images matching selections -FILTER- were found'
            return,''
        ENDELSE
     ENDIF

     if keyword_set(infov) or keyword_set(high_c) then object='PARTIAL FOV'
     obj_str = ['PARTIAL FOV','FULL FOV','DARK', 'CAL LAMP']
     IF keyword_set(object) THEN BEGIN
;       obj_num=where(obj_str EQ strupcase(object))
;       IF obj_num(0) EQ -1 and strlen(object) EQ 1 THEN obj_num=fix(object)
;       sel=where(entry(records-1).object EQ obj_num(0))
        IF strlen(object) EQ 1 THEN object = obj_str(fix(object)) else $
          object=strupcase(object)
        sel=where(strupcase(eit_fxpar(entry(records-1),'object')) EQ object)
        sel_index=where_arr(select,sel,cnt)
        IF cnt ne 0 THEN select=select(sel_index) ELSE BEGIN
            message,/info,'No images matching selections -OBJECT- were found'
            return,''
        ENDELSE
     ENDIF

     IF keyword_set(high_c) THEN BEGIN
        sel=where(eit_fxpar(entry(records-1),'n_repeat') gt 5)
        sel_index=where_arr(select,sel,cnt)
        IF cnt ne 0 THEN select=select(sel_index) ELSE BEGIN
            message,/info,'No high cadence subfield images were found'
            return,''
        ENDELSE
     ENDIF

     IF keyword_set(nx) THEN BEGIN
;       sel=where(entry(records-1).nx EQ nx/32)
        sel=where(eit_fxpar(entry(records-1),'naxis1') EQ nx)
        sel_index=where_arr(select,sel,cnt)
        IF cnt ne 0 THEN select=select(sel_index) ELSE BEGIN
            message,/info,'No images matching selections -NX- were found'
            return,''
        ENDELSE
     ENDIF
     IF keyword_set(ny) THEN BEGIN
;       sel=where(entry(records-1).ny EQ ny/32)
        sel=where(eit_fxpar(entry(records-1),'naxis2') EQ ny)
        sel_index=where_arr(select,sel,cnt)
        IF cnt ne 0 THEN select=select(sel_index) ELSE BEGIN
            message,/info,'No images matching selections -NY- were found'
            return,''
        ENDELSE
     ENDIF

     IF keyword_set(xbin) THEN BEGIN
;       sel=where(entry(records-1).nx_sum EQ xbin)
        nx_sum=(eit_fxpar(entry(records-1),'p2_x')- $
           eit_fxpar(entry(records-1),'p1_x')+1)/eit_fxpar(entry(records-1),$
            'naxis1')
        sel=where(nx_sum eq xbin)
        sel_index=where_arr(select,sel,cnt)
        IF cnt ne 0 THEN select=select(sel_index) ELSE BEGIN
            message,/info,'No images matching selections -XBIN- were found'
            return,''
        ENDELSE
     ENDIF
     IF keyword_set(ybin) THEN BEGIN
;       sel=where(entry(records-1).ny_sum EQ ybin)
        ny_sum=(eit_fxpar(entry(records-1),'p2_y')- $
           eit_fxpar(entry(records-1),'p1_y')+1)/eit_fxpar(entry(records-1),$
            'naxis2')
        sel=where(ny_sum eq ybin)
        sel_index=where_arr(select,sel,cnt)
        IF cnt ne 0 THEN select=select(sel_index) ELSE BEGIN
            message,/info,'No images matching selections -YBIN- were found'
            return,''
        ENDELSE
     ENDIF

     IF keyword_set(sci_obj) THEN BEGIN
        scis = strupcase(eit_fxpar(entry(records-1),'sci_obj'))
        sel=where(strpos(scis,strupcase(sci_obj)) ne -1)
        sel_index=where_arr(select,sel,cnt)
        IF cnt ne 0 THEN select=select(sel_index) ELSE BEGIN
            message,/info,'No images matching selections -SCI_OBJ- were found'
            return,''
        ENDELSE
     ENDIF

     IF keyword_set(nocals) AND NOT keyword_set(sci_obj) THEN BEGIN
        scis = strupcase(eit_fxpar(entry(records-1),'sci_obj'))
        dum = where((strpos(scis,'CALIBRATION LAMP') ne -1) OR $
                    (strpos(scis,'DARK IMAGE') ne -1), complement=sel)
        sel_index=where_arr(select,sel,cnt)
        IF cnt ne 0 THEN select=select(sel_index) ELSE BEGIN
            message,/info,'No images matching selections -NOCALS- were found'
            return, ''
        ENDELSE
     ENDIF


     IF keyword_set(infov) THEN BEGIN
        cdelt = eit_pixsize()
        xcen = 505 + 1
        ycen = 511 + 20
        repnt = utc2sec(anytim2utc('16-apr-1997 23:30'))
        early = where(obstime(select) lt repnt)
        if early(0) ne -1 then begin
            ycen = intarr(n_elements(select)) + ycen
            ycen(early) = ycen(early) + 76
        endif
        p1x = (eit_fxpar(entry(records(select)-1),'P1_X') - xcen) * cdelt
        p1y = (eit_fxpar(entry(records(select)-1),'P1_Y') - ycen) * cdelt
        p2x = (eit_fxpar(entry(records(select)-1),'P2_X') - xcen) * cdelt
        p2y = (eit_fxpar(entry(records(select)-1),'P2_Y') - ycen) * cdelt
        sel = where(infov(0) ge p1x and infov(0) le p2x and $
                     infov(1) ge p1y and infov(1) le p2y,cnt)
        IF cnt ne 0 THEN select = select(sel) ELSE BEGIN
            message,/info,'No images matching selections -INFOV- were found'
            return,''
        ENDELSE
     ENDIF

     records=records(select)
     u_rec=n_elements(select)
     index=tag_exist(entry(0),'simple')

  IF text and not index THEN BEGIN
       loop_num=fix(u_rec/1024)
       for i=0,loop_num do BEGIN
           IF i EQ loop_num THEN top_dum=u_rec ELSE top_dum=1024l*i+1024
           short_rec=records(1024l*i:top_dum-1)
           short_cat = cat_to_text(entry(short_rec-1),short=short,lz=lz,web=web)
           IF i gt 0 THEN cat_user=[cat_user,short_cat] ELSE cat_user=short_cat
       endfor
  ENDIF ELSE IF keyword_set(ss) and index then cat_user = records-1 else $
       cat_user = entry(records-1)

  ; Return specifically requested keywords

  IF n_elements(filename) gt 0 THEN BEGIN
     if tag_exist(entry,'file_name') then filename = $
        (strlowcase(entry.file_name))(records-1) ELSE $
        filename = eit_fxpar(entry(records-1),'filename')
  ENDIF
  IF n_elements(tai) gt 0 THEN BEGIN
     if tag_exist(entry,'obs_time') then tai = $
            (utc2tai({mjd:entry.obs_time.mjd+49718, $
	   	   time:entry.obs_time.sec*1000L}))(records-1) ELSE $
        tai = utc2tai(anytim2utc(temporary(eit_fxpar(entry(records-1),$
           'date_obs'))))
  ENDIF

  if not lz then delvarx, entry

RETURN, cat_user
END

;------------------------------------------------------------------------------
; subprocedure to kill the help window
;------------------------------------------------------------------------------
PRO killhelp
COMMON helpshare,helpbase
WIDGET_CONTROL, helpbase, /DESTROY
END
;------------------------------------------------------------------------------
; subwidget to display a help window with text output
;------------------------------------------------------------------------------
PRO helpcat
COMMON helpshare,helpbase
helparray = strarr(21)
helparray(0)='      This is the SOHO - EIT Level Zero Catalog.'
helparray(1)='  '
helparray(2)=' This tool is a widget interface to the EIT Level Zero'
helparray(3)=' catalog. EIT_CATRD is a function that returns a listing'
helparray(4)=' of catalog files matching the selected parameters.'
helparray(5)=' Additionally, the file names and observation times in'
helparray(6)=' TAI format can be returned. The widget will also display'
helparray(7)=' the results of the selected search.'
helparray(8)='  '
helparray(9)=' Search Parameters: '
helparray(10)='   String or Raw output: raw = IDL structure, string=default'
helparray(11)='   Full or Short Listing: short=default= < 80 characters'
helparray(12)='   Date Parameter: enter specIFic date or relative, y=5 '
helparray(13)='   Start/Stop Date: enter range of dates to select from'
helparray(14)='   NX, NY: enter image size in pixels'
helparray(15)='   XBIN, YBIN: enter amount of pixel summing'
helparray(16)='   WAVE: enter 171,195,284,304 or 1-4'
helparray(17)='   FILTER: enter one:[AL+1,BLK EST,CLEAR,BLK WST,AL+2] or 0-5'
helparray(18)='   OBJECT: enter one:[FULL FOV,PARTIAL FOV,DARK,CAL LAMP] or 0-4'
helparray(19)='   SCI_OBJ: enter any portion of keyword to search on'
helparray(20)='   INFOV: enter solar coods (arcsecs), in Partial FOV'
;
helpbase = WIDGET_BASE(TITLE = 'EIT LZ Catalog Help', /FRAME, /COLUMN, $
	XOFFSET = 350, YOFFSET = 150)
finishbutton = WIDGET_BUTTON(helpbase, VALUE = 'Click here when done', $
	UVALUE = 'donehelp')
helptext = WIDGET_TEXT(helpbase, VALUE = helparray, XSIZE = 58, YSIZE = 19)
WIDGET_CONTROL, helpbase, /REALIZE
XMANAGER, 'helpcat', helpbase, EVENT_HANDLER='CATDISP_event',MODAL = helpbase
END

;------------------------------------------------------------------------------
; event handling procedure
;------------------------------------------------------------------------------
PRO catdisp_Event, Event
COMMON cat_params,nxp,nyp,xbinp,ybinp,wavep,filtp,start_dp,stop_dp,date_par,list
COMMON cat_par2,shortp,longp,rawp,objp,file_par,ret_file,ret_tai,tai_par,list7
COMMON cat_par3,str_par,scip,fovxp,fovyp,highc

   WIDGET_CONTROL,Event.Id,GET_UVALUE=Ev

   CASE Ev OF

   'donehelp': killhelp

   'bgroup1': IF event.value EQ 1 THEN rawp=1 ELSE rawp=0

   'bgroup2': IF event.value EQ 1 THEN shortp=1 ELSE shortp=0

   'bgroup4':  IF event.select EQ 1 THEN highc=1 ELSE highc=0

   'BGROUP3': BEGIN
       CASE Event.Value OF
       0: BEGIN
           widget_control,date_par,get_value=date
           widget_control,start_dp,get_value=start_d
           widget_control,stop_dp,get_value=stop_d
           widget_control,nxp,get_value=nx
           widget_control,nyp,get_value=ny
           widget_control,xbinp,get_value=xbin
           widget_control,ybinp,get_value=ybin
           widget_control,wavep,get_value=wave
           widget_control,filtp,get_value=filter
           widget_control,objp,get_value=object
           widget_control,scip,get_value=sci_obj
           widget_control,fovxp,get_value=fovx
           widget_control,fovyp,get_value=fovy
           if fovx(0) ne '' and fovy(0) ne '' then infov = fix([fovx,fovy]) $
              else infov = ''
           IF ret_file THEN file_par=''
           IF ret_tai THEN tai_par=''
           widget_control,/hourglass
           list=search_cat(date(0), long=longp, raw=rawp, yester=yester, /lz, $
		      no_next=no_next, short=shortp, input_file=input_file, $
		      records=records, filename=file_par, tai=tai_par, $
                       start_date=start_d(0),stop_date=stop_d(0),nx=fix(nx(0)),$
                       wave=fix(wave(0)),filter=filter(0),ny=fix(ny(0)),$
                       xbin=fix(xbin(0)),ybin=fix(ybin(0)),object=object(0),$
                       cat_struct=str_par,ss=ss,sci_obj=sci_obj(0),infov=infov,$
                       high_c=highc)
           IF rawp THEN widget_control,list7,set_value=$
               cat_to_text(list,short=shortp,/lz) ELSE $
               widget_control,list7,set_value=list
           widget_control,hourglass = 0
          END
       1: BEGIN
           OPENW,lun,/get_lun,'cat.list'
           IF rawp THEN PRINTF,lun,cat_to_text(list,/lz,short=shortp) $
                ELSE PRINTF,lun,list
           FREE_LUN,lun
           xmessage,'file dumped to cat.list',wait=2,title='File Create'
          END
       2: WIDGET_CONTROL, /DESTROY, event.top
       3: helpcat
       ELSE:
      ENDCASE
   END
END
END

;------------------------------------------------------------------------------
;+
; NAME        :
;               EIT_CATRD
; PURPOSE     : Read the daily catalogs and return entries as requested output
;
; CATEGORY    : Catalogs
;
; EXPLANATION : This function reads the daily QKL catalogs or the single
;               Level Zero catalog.
;
; SYNTAX      : list = eit_catrd(in_date, group=group, interactive=interactive,
;               date, long=long, raw=raw, yester=yester, lz=lz,
;	       no_next=no_next, short=short, input_file=input_file,
;	       records=records, filename=filename, tai=tai,
;               start_date=start_date,stop_date=stop_date,object=object,
;               wave=wave,filter=filter,nx=nx,ny=ny,xbin=xbin,ybin=ybin,
;               timerange=timerange,sci_obj=sci_obj,infov=infov,hihg_c=high_c)
;
; EXAMPLES    : return string listing of all LZ 304 images from Jun 2, 1996
;               to June 22, 1996 taken in the clear filter and return
;               filenames,
;                IDL> file=''
;                IDL> list=eit_catrd(start_date='2-jun-96',stop_date=$
;                        '22-jun-96',wave='304',filter='clear',file=file)
;
; CALLED BY   : top level
;
; CALLS TO    : timegrid, str_copy_tags, cat_open, cat_directory,
;               cat_to_text, where_arr, anytim2utc, utc2doy, doy2utc,
;               xmessage, utc2tai
;
; ARGUMENTS   :
;	DATE	IF present, a string date in the format "yyyy/mm/dd"
;		of the daily catalog to be searched.
;		Default is the date of the most recent catalog.
;
; KEYWORDS    :
;	INPUT_FILE  IF present, this is the catalog which is read in.
;		    This may be any of the catalog: "merged", QKL daily or
;		    LZ daily.   Default is the "merged" catalog.
;       LZ      IF present read from the merged Level-zero catalog
;	YESTER  IF present, indicates the number of 'days/catalogs' backward
;		in time you want as the catalog input.  Note that this is
;		really the number of backward catalogs, so days may not
;		line up as expected, but they should.
;		New feature:   print,catrd_daily("y=3") for three days ago.
;	NO_NEXT IF present and set THEN return a null string IF the specIFied
;		date does not have a catalog.
;	SHORT_TEXT IF present and set and TEXT is the output mode then the
;		displayed text will fit in 80 characters w/ less info.
;	RECORDS IF present, then return catalog file record numbers matching
;		the entries in the returned variable.  This is the VMS
;		record number.
;	LONG    IF present and set, then all catalog entries are considered,
;		including duplicates and entries are left in unsorted,
;		reform order.
;	RAW    IF present and set , return the catalog entries as the raw
;		data structure instead of the default of a strarr of text
;		entries.
;		NOTE: the default is to return a string array of entries.
;	FILENAME  IF present, then return the fits file names matching
;		  the entries in the returned variable.
;	TAI      IF present, then return the TAI time matching
;		 the entries in the returned variable.
;       START_DATE IF present and a LZ listing then sets start date of list
;       STOP_DATE  IF prsent and a LZ listing then sets end date of list
;       WAVE      Return matches from LZ/QKL catalog (171,195,284,304 or 1-4)
;       FILTER    Return matches from LZ/QKL catalog (0-4 or one of:
;                    ['AL+1', 'BLK EST',  'CLEAR', 'BLK WST', 'AL+2' ] )
;       NX        Return matches from LZ/QKL catalog for xsize in pixels
;       NY        Return matches from LZ/QKL catalog for ysize in pixels
;       XBIN      Return matches from LZ/QKL catalog for x summing in pixels
;       YBIN      Return matches from LZ/QKL catalog for y summing in pixels
;       TIMERANGE 2 element vector containing start and stop dates
;       OBJECT    IF present select object, dark, cal lamp, full FOV,
;                 partial FOV
;       CAT_STRUCT An alternate input, a raw catalog structure previsouly
;                  created - useful to get search tools, if input is
;                 a index structure will return output structure not text
;       SS        Return subscripts of input index structure instead of
;                 selected structure
;       SCI_OBJ   Return matches from LZ/QKL catalog for entered keyword
;       NOCALS    Filter out calibration lamps or dark images
;       INFOV     Return matches (partial FOV) if entered coordinates,
;                 Solar arcsecs, is in field of view, e.g, [1,-960]=south pole
;       HIGH_C    Set if want high cadence (defined to be greater than 5
;                 images per file) subfield images
;
; OUTPUTS     :
;	Return a string arrar of catalog entries, unless the /RAW keyword
;	is set then return raw structure of entries.
;	IF the /LONG keyword is set then return all catalog entries and
;	do not sort.
;	IF input is index structure returns output structure
;
; COMMON      : cat_params, cat_par2, helpshare
;
; RESTRICTIONS: none
;
; SIDE EFFECTS: none
;
; PROJECT     : SOHO - EIT
;
; HISTORY     : V1,  Elaine Einfalt (HSTX)
;		1996 March 31, added /NO_NEXT keyword
;		1996 May 13, allow YESTER to use numerical values
;
;               V2, Jeff Newmark - complete revision, LZ catalog, widget
;                    interface, etc...
;               1996 Dec 23 - add selection over times as well as dates
;                    J Newmark
;               1996 Jan 15 - changed date variable to indate due to
;                    conflict with IDLASTRO function date!
;               1996 Jan 16 - use eit_fxpar to obtain selection parameters
;                    allow cat_struct input to be index structures
;                    created by read_eit as well as raw catalog structures
;               V3.0
;               1997 Mar 20 J. Newmark - add in sci_obj field for catalog
;               1997 Jun 03 J. Newmark - fix bug in wavelength selection
;               1998 Jan 20 J. Newmark - add infov keyword
;               V3.1
;               1998 Apr 01 J. Newmark - automatic selection of LZ vs. QKL
;               1998 Apr 07 J. Newmark - allow mixed LZ + QKL
;               1998 Oct 23 J. Newmark - add high_c keyword
;		1999 Oct 15 R.D.Bentley - Try EIT_LZ_CAT before defaulting to EIT_LZ for catalog
;               2000 Jan 19 J. Newmark - bug fix in little used path
;Version 2.1
;		2003 February 13 D.M. fecit - Added handling of big-endian OSes.
;		2006 October 7	 F. Auchère - Added a fallback when no QKL catalogs are found.
;									- Added the nocals keyword to filter out calibration data
;
; CONTACT     : gurman@gsfc.nasa.gov
;-
FUNCTION eit_catrd, date, group=group, interactive=interactive,$
                long=long, raw=raw, yester=yester, lz=lz, $
	       no_next=no_next, short=short, input_file=input_file, $
	       records=records, filename=filename, tai=tai, web=web, $
                start_date=start_date,stop_date=stop_date, object=object,$
                wave=wave,filter=filter,nx=nx,ny=ny,xbin=xbin,ybin=ybin,$
                timerange=timerange,cat_struct=cat_struct,ss=ss,$
                sci_obj=sci_obj,infov=infov,uncommon=uncommon,high_c=high_c,$
                nocals=nocals

COMMON cat_params,nxp,nyp,xbinp,ybinp,wavep,filtp,start_dp,stop_dp,date_par,list
COMMON cat_par2,shortp,longp,rawp,objp,file_par,ret_file,ret_tai,tai_par,list7
COMMON cat_par3,str_par,scip,fovxp,fovyp,highc


   recursive = 0
   IF n_elements(input_file) EQ 0 and not keyword_set(interactive) THEN BEGIN
      if IS_GSFCVMS() eq 1 then lz_cat='cat_dir:lz_catalog.cat' $
;;       else lz_cat=concat_dir(getenv('EIT_LZ'),'lz_catalog.cat')
      else begin
          cat_dir = get_logenv('EIT_LZ_CAT')
          if cat_dir ne '' then lz_cat=concat_dir(cat_dir,'lz_catalog.cat') $
          else lz_cat=concat_dir(getenv('EIT_LZ'),'lz_catalog.cat')
      endelse
      openr,cat_unit,lz_cat,/get_lun
      stat=fstat(cat_unit)
      point_lun,cat_unit,stat.size-128
      cat=bytarr(128)
      readu,cat_unit,cat
      free_lun,cat_unit
;
; Handle big-endian OSes
;
      mjd_tai = fix(cat,15) & mjd_tai_0 = mjd_tai
      byteorder, mjd_tai, /swap_if_big
      if mjd_tai ne mjd_tai_0 then begin
         offsets = 2l^[0, 8, 16]
         seconds_tai = long(total(offsets*cat(17:19)))
      endif else seconds_tai = long(cat, 17)
      msec_tai = 1000l*seconds_tai
;
;    obs_time={mjd:fix(cat,15)+49718l,time:long(cat,17)*1000l}
;
      obs_time={mjd:mjd_tai + 49718l, time:msec_tai}
;
      lz_date_end = anytim2utc(obs_time)
      case 1 of
        keyword_set(timerange): date_comp = anytim2utc(timerange(1))
        keyword_set(stop_date): date_comp = anytim2utc(stop_date)
        keyword_set(date): date_comp = anytim2utc(date)
        keyword_set(yester): date_comp = $
               anytim2utc(doy2utc(utc2doy(anytim2utc(!stime))-yester))
        else: date_comp = anytim2utc(!stime)
      endcase
      if date_comp.mjd le lz_date_end.mjd then lz = 1 else begin
         if keyword_set(timerange) then date_comp = anytim2utc(timerange(0))
         if keyword_set(start_date) then date_comp = anytim2utc(start_date)
         if date_comp.mjd le lz_date_end.mjd then begin
              recursive = 1
              lz = 1
              if keyword_set(timerange) THEN start_date=timerange(0)
              temp_date=anytim2utc(lz_date_end,/vms)
              recur=search_cat(date, long=long, raw=raw, yester=yester, lz=lz, $
		      no_next=no_next, short=short, input_file=input_file, $
		      records=records, filename=filename, tai=tai, $
                       start_date=start_date,stop_date=temp_date,web=web,$
                       wave=wave,filter=filter,nx=nx,ny=ny,xbin=xbin,$
                       ybin=ybin,object=object,cat_struct=cat_struct,ss=ss,$
                       sci_obj=sci_obj,infov=infov,uncommon=uncommon,$
                       high_c=high_c, nocals=nocals)
              lz = 0
              if n_elements(filename) ne 0 then rfilename = temporary(filename)
              lz_date_end = {mjd:lz_date_end.mjd + 1,time:0l}
              if keyword_set(timerange) THEN stop_date=timerange(1)
              timerange = [anytim2utc(lz_date_end,/vms),stop_date]
         endif else lz = 0
      endelse
    ENDIF

   IF keyword_set(cat_struct) THEN str_par=cat_struct ELSE str_par = 0
   IF not keyword_set(interactive) THEN BEGIN
       IF keyword_set(timerange) and not keyword_set(lz) THEN BEGIN
           raw=keyword_set(raw)
           date=anytim2utc(timerange(0),/vms,/date)
           date2=anytim2utc(timerange(1),/vms,/date)
           filex=''
           grid=timegrid(date,date2,/day,/string)
           numdays = n_elements(grid)
           idx = 0
           list = ''
           for i=0,numdays-1 do BEGIN
              if numdays eq 1 then begin
                  start_date = timerange(0)
                  stop_date = timerange(1)
              endif else case i of
                  0: begin
                      start_date = timerange(0)
                      stop_date  = date + ' 23:59:59'
                     end
                  n_elements(grid)-1: begin
                      start_date  = date2 + ' 00:00:00'
                      stop_date = timerange(1)
                     end
                  else: begin
                      start_date  = 0
                      stop_date = 0
                        end
               endcase

              new=search_cat(grid(i), long=long, raw=raw, yester=yester, lz=lz, $
		      no_next=no_next, short=short, input_file=input_file, $
		      records=recordsx, filename=filex, tai=tai, $
                       start_date=start_date,stop_date=stop_date,web=web, $
                       wave=wave,filter=filter,nx=nx,ny=ny,xbin=xbin,$
                       ybin=ybin,object=object,cat_struct=cat_struct,ss=ss,$
                       sci_obj=sci_obj,infov=infov,high_c=high_c, nocals=nocals)
              IF N_ELEMENTS(recordsx) GT 0 THEN BEGIN
                IF idx EQ 0 THEN BEGIN
                      records=recordsx
                      filename=filex
                      list=new
                      idx = 1
                ENDIF ELSE BEGIN
                    filename=[temporary(filename),filex]
                    records=[temporary(records),recordsx]
                ENDELSE
                IF raw and i ne 0 THEN BEGIN
                   out_str=list(0)
                   if datatype(new) ne 'STR' then $
                     list=[str_copy_tags(out_str,list),str_copy_tags(out_str,new)]
                ENDIF ELSE IF i ne 0 THEN list=[list,new]
              ENDIF
          endfor
       ENDIF ELSE BEGIN
           IF keyword_set(timerange) THEN BEGIN
              start_date=timerange(0)
              stop_date=timerange(1)
           ENDIF
           list=search_cat(date, long=long, raw=raw, yester=yester, lz=lz, $
		      no_next=no_next, short=short, input_file=input_file, $
		      records=records, filename=filename, tai=tai, $
                       start_date=start_date,stop_date=stop_date,web=web,$
                       wave=wave,filter=filter,nx=nx,ny=ny,xbin=xbin,$
                       ybin=ybin,object=object,cat_struct=cat_struct,ss=ss,$
                       sci_obj=sci_obj,infov=infov,uncommon=uncommon,$
                       high_c=high_c, nocals=nocals)
       ENDELSE

       if recursive then begin
         if datatype(list) ne 'STR' then list = [str_copy_tags(out_str,recur),$
             str_copy_tags(out_str,list)] else list = [recur,list]
         if n_elements(rfilename) ne 0 then filename = [rfilename,temporary(filename)]
       endif
       RETURN, list
   ENDIF

   IF n_elements(group) EQ 0 THEN group=0
   IF n_elements(filename) ne 0 THEN ret_file=1 ELSE ret_file=0
   IF n_elements(tai) ne 0 THEN ret_tai=1 ELSE ret_tai=0

   catdisp = WIDGET_BASE(GROUP_LEADER=Group, COLUMN=1, MAP=1, $
       TITLE='EIT Level Zero Catalog', UVALUE='catdisp')

   topbtns = ['SEARCH','Save to File','Done','Help' ]
   BGROUP3 = CW_BGROUP( catdisp, topbtns, ROW=1, UVALUE='BGROUP3')

   tmp = WIDGET_LABEL(catdisp, value='Search Parameters')

   rawp=0
   btns = ['String output','Raw output']
   bgroup1 =cw_bgroup(catdisp,btns,row=1,/exclusive,set_value=0,/frame,$
        uvalue='bgroup1')

   shortp=1
   btns = ['Full listing','Short listing']
   bgroup2 =cw_bgroup(catdisp,btns,row=1,/exclusive,set_value=1,/frame,$
        uvalue='bgroup2')

   tmp = WIDGET_BASE(catdisp, /row)
   date_par = cw_field(tmp, title=' DATE PARAMETER', xsize=10, value=' ')
   start_dp = cw_field(tmp, title=' START_DATE', xsize=15, value=' ')
   stop_dp = cw_field(tmp, title=' STOP_DATE', xsize=15, value=' ')
   tmp = WIDGET_BASE(catdisp, /row)
   nxp = cw_field(tmp, title=' NX', xsize=5, value=' ')
   nyp = cw_field(tmp, title=' NY', xsize=5, value=' ')
   xbinp = cw_field(tmp, title=' XBIN', xsize=2, value=' ')
   ybinp = cw_field(tmp, title=' YBIN', xsize=2, value=' ')
   tmp = WIDGET_BASE(catdisp, /row)
   wavep = cw_field(tmp, title=' WAVE', xsize=5, value=' ')
   filtp = cw_field(tmp, title=' FILTER', xsize=10, value=' ')
   objp = cw_field(tmp, title=' OBJECT', xsize=12, value=' ')
   tmp = WIDGET_BASE(catdisp, /row)
   scip = cw_field(tmp, title=' SCI_OBJ', xsize=25, value=' ')
   fovxp = cw_field(tmp, title=' IN_FOV X (arcsecs)', xsize=5, value='')
   fovyp = cw_field(tmp, title=' IN_FOV Y (arcsecs)', xsize=5, value='')

   tmp = WIDGET_BASE(catdisp, /row, /nonexclusive)
   bgroup4 = widget_button(tmp,value='High Cadence Subfields',$
             /frame,uvalue='bgroup4',xsiz=6,units=2)

   LABEL16 = WIDGET_LABEL(catdisp,UVALUE='LABEL16',VALUE='LZ Catalog Listing')

   lfont = '-misc-fixed-medium-r-normal--20-140-100-100-c-100-iso8859-1'
;  lfont = '-misc-fixed-bold-r-normal--15-120-100-100-c-90-iso8859-1'
   lfont = (get_dfont(lfont))(0)
   IF lfont EQ '' THEN lfont = 'fixed'
   LIST7 = WIDGET_TEXT( catdisp,VALUE='', XSIZE=90, UVALUE='LIST7',YSIZE=10,$
           font=lfont,/scroll)

   WIDGET_CONTROL, catdisp, /REALIZE
   XMANAGER, 'catdisp', catdisp, /modal

   IF ret_file THEN filename=file_par
   IF ret_tai THEN tai=tai_par

RETURN,list
END


Web curator: Frédéric Auchère
Responsible NASA official: Joseph B. Gurman, Facility Scientist, Solar Data Analysis Center
joseph.b.gurman@gsfc.nasa.gov
+1 301 286-4767
NASA Goddard Space Flight Center
Solar Physics Branch / Code 682

Last revised: - Wed May 9 21:44:59 2007- F. Auchère