EIT Software Listings

 

anal
obsolete
response
util

 

Previous Routine
Next Routine

 

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

 


;+
; NAME:
;	EIT_DISPLAY
;
; PURPOSE:
;	This function will display EIT movies (IDL Save Sets) and
;       EIT images (FITS files) using eit_movie and eit_image
;       respectively.
;
; CATEGORY:
;	WIDGET interface
;
; CALLING SEQUENCE:
;       EIT_DISPLAY
;
; INPUTS:  None, presently this routine reads predefined directories
;	         namely the logical REF_DIR (FITS images) or MOVIE_DIR
;                (3-dim IDL Save Sets).
;
; KEYWORD PARAMETERS: None
;
; OUTPUTS:
;	This routine displays images. It does not return any outputs.
;
; COMMON BLOCKS:
;       filestuff,dirspec,flist,index,list7,text6 - this common block is
;         used to pass back and forth to the event handler the
;         directory, filelist, file index, file widget and directory widget.
;       helpshare,helpbase - a common block for the help widget
;
; SIDE EFFECTS:
;	unsure if common block must be re-initialized after each run.
;
; RESTRICTIONS:
;	Serious memory hog, especially if display movies
;
; PROCEDURE:
;	A widget is displayed. The user can choose either IDL Save
;       Sets (assumed therefore to be movies) or FITS files (assumed
;       to be images). The user then selects a file to display using
;       the appropriate mechanism. The user can zoom an image. This
;       calss the widget cw_zoom.
;
; MODIFICATION HISTORY:
; 	Written by:  J. Newmark 	Date.  Feb. 1996
;		     1996 march 14 - E. Einfalt - changed title banner
;                    1996 june 12 - J. Newmark - use catalog for image
;                             listings, add RDPIX function
;                    1996 june 20 - J. Newmark - enable use of "efz" files
;                    1996 july 8 - J. Newmark - add print button
;                    1996 july 19 - J. Newmark - added calls to eit_file2path
;                             to get directory names and pathways, allow
;                             for collapsed data trees
;                    1996 aug 20 - J. Newmark - added ability to display
;                             LZ 3-D data
;                    1996 nov 26 - D.M. fecit - added /flat to all EIT_IMAGE
;                             calls
;                    1996 dec 3 - J. Newmark - added button for MOVIE_ARCHIVE
;
;                    1997 mar 12 - D.M. fecit - changed exposure time strings
;                             to floating point
;                    2003 may 2  - C.A. Young - Added year droplist to select
;                              the year subdirectory in new movie archive
;		     2003 may 5 - E Einfalt - Added VMS compatibility to yearly
;			       subdirectory code
;                    2003 may 5 - D.M. fecit - Modified annual movie directory
;                              dropdown code to accommodate years other than
;                              2003.
;                    2003 jul 29 - D.M. fecit - Modified default YSIZE of
;                              file list in main widget to allow view of more
;                              file names.
;
;-
;------------------------------------------------------------------------------
; subprocedure to kill the help window
;------------------------------------------------------------------------------
PRO killhelp
COMMON helpshare,helpbase
WIDGET_CONTROL, helpbase, /DESTROY
END
;------------------------------------------------------------------------------
; subprocedure to kill the zoom window
;------------------------------------------------------------------------------
PRO killzoom
COMMON zoomshare,zbase
WIDGET_CONTROL, zbase, /DESTROY
END
;------------------------------------------------------------------------------
; subwidget to display a help window with text output
;------------------------------------------------------------------------------
PRO helpout
COMMON helpshare,helpbase
helparray = strarr(20)
helparray(0)='           This is the SOHO - EIT Display System.'
helparray(1)='  '
helparray(2)=' This tool will display FITS images using EIT_IMAGE or '
helparray(3)=' Movies (IDL Save Sets) using EIT_MOVIE. The default path'
helparray(4)=' for files is the image directory defined by the logical'
helparray(5)=' REF_DIR (or LZ_DIR). The full path will show in the directory'
helparray(6)=' box. The list widget will show the file listing. An image can'
helparray(7)=' be displayed by either double-clicking on the filename or'
helparray(8)=' single-clicking on the filename and choosing the DISPLAY'
helparray(9)=' button. The FITS image can be zoomed by single-clicking on'
helparray(10)=' the filename and choosing the ZOOM button. The directory'
helparray(11)=' can be changed by either editing the DIRECTORY widget or'
helparray(12)=' toggling IMAGE button (logical REF_DIR, LZ_DIR) and the'
helparray(13)=' MOVIE button (logical MOVIE_DIR). '
helparray(14)='    Other useful functions acting on FITS images include'
helparray(15)=' RDPIX to give pixel information and PRINT which produces'
helparray(16)=' a POSTSCRIPT image. A SELECT DATE box is provided for'
helparray(17)=' selecting specific days. This is a front end to EIT_CATRD'
helparray(18)=' and allows the same kind of inputs, e.g. /y,y=3,10-Jul-96, '
helparray(19)=' a blank gives today, many other allowed date formats.'
;
helpbase = WIDGET_BASE(TITLE = 'EIT Display 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 = 55, YSIZE = 20)
WIDGET_CONTROL, helpbase, /REALIZE
XMANAGER, 'helpout', helpbase, EVENT_HANDLER='EITDISP_event',MODAL = helpbase
END
;------------------------------------------------------------------------------
; sub-procedure to get directory name for saving a postscript image
;------------------------------------------------------------------------------
pro save_psdir
common psstuff,save_dir
COMMON helpshare,helpbase
lfont = '-misc-fixed-medium-r-normal--20-140-100-100-c-100-iso8859-1'
lfont = (get_dfont(lfont))(0)
IF lfont EQ '' THEN lfont = 'fixed'
helpbase = WIDGET_BASE(TITLE = 'Postscript File', /FRAME, /COLUMN, $
	XOFFSET = 350, YOFFSET = 150)
finishbutton = WIDGET_BUTTON(helpbase, VALUE = 'Accept',UVALUE = 'donehelp')
hdr='Enter directory for output PS file:'
helptext = WIDGET_TEXT(helpbase, VALUE = hdr, XSIZE = 65, YSIZE =1, $
                  font=lfont, /SCROLL)
if !version.os eq 'vms' then save_dir='[EIT.PR]' else begin
     cd,current=save_dir
     save_dir=save_dir+'/'
endelse
SDIR = WIDGET_TEXT(helpbase ,VALUE=save_dir,EDITABLE=1, UVALUE='SDIR',YSIZE=1)
WIDGET_CONTROL, helpbase, /REALIZE
XMANAGER, 'save_psdir', helpbase, EVENT_HANDLER='EITDISP_event',MODAL = helpbase
end
;------------------------------------------------------------------------------
; sub-procedure to display FITS header
;------------------------------------------------------------------------------
pro disphd,filename
COMMON helpshare,helpbase
;
lfont = '-misc-fixed-medium-r-normal--20-140-100-100-c-100-iso8859-1'
lfont = (get_dfont(lfont))(0)
IF lfont EQ '' THEN lfont = 'fixed'
hdr=headfits(filename)
helpbase = WIDGET_BASE(TITLE = filename, /FRAME, /COLUMN, $
	XOFFSET = 350, YOFFSET = 150)
finishbutton = WIDGET_BUTTON(helpbase, VALUE = 'Click here when done', $
	UVALUE = 'donehelp')
helptext = WIDGET_TEXT(helpbase, VALUE = hdr, XSIZE = 65, YSIZE = 24, $
                  font=lfont, /SCROLL)
WIDGET_CONTROL, helpbase, /REALIZE
XMANAGER, 'disphd', helpbase, EVENT_HANDLER='EITDISP_event',MODAL = helpbase
END

;------------------------------------------------------------------------------
;  creates a zoom widget (cw_zoom). Uses eit_image to read in FITS image.
;  loads appropriate color table.
;------------------------------------------------------------------------------
pro mkzoom,filename
COMMON zoomshare,zbase
;
    sector = ['171', '195', '284', '304']
    fits_header=headfits(filename)
    naxis=eit_fxpar(fits_header,'NAXIS')
    if naxis eq 3 then begin
       nimgs=eit_fxpar(fits_header,'NAXIS3')
       comms=eit_fxpar(fits_header,'COMMENT')
       start=where(strpos(comms,'BEGIN MULTIPLE') ne -1)
       out=strarr(nimgs+7)
       out(0)='Please select from the list of images below:'
       out(1)='      Image numbers range from 0-'+strtrim(nimgs-1,2)
       out(3:nimgs+6)=comms(start(0):start(0)+3+nimgs)
       answer='0'
       xin,answer,out,status=status
       if status eq 0 then return
       if strupcase(answer(0)) eq 'ALL' then begin
          out(0)='PLEASE SELECT ONLY 1 IMAGE !!!'
          xin,answer,out,status=status
       endif
       if status eq 0 then return
       if strupcase(answer(0)) eq 'ALL' then answer(0)='0'
       image_no=fix(answer(0))
       img = eit_image(filename,repl=eit_dark(),dark=eit_dark(),$
                     v_off=v_off,origin=origin,image_no=image_no, /flat)
       wave=eit_fxpar(fits_header,'WAV',image_no=image_no)
       wave=strtrim(wave(0),2)
    endif else begin
       img = eit_image(filename,v_off=46,dark=eit_dark(),repl=eit_dark(), $
                /flat)
       wave=strtrim(eit_fxpar(fits_header,'WAVELNTH'),2)
    endelse
    for j_wave = 0, 3 do if wave eq sector(j_wave) then i_wave = j_wave
    loadct,42 + i_wave,file=getenv('coloreit')
    sz=size(img)
    zbase=widget_base(/column)
    zoom=cw_zoom(zbase,xsize=sz(1),ysize=sz(2),x_scr=512<sz(1),y_scr=512<sz(2),$
       uvalue='zoomdone',/track,/sample)
    done=widget_button(zbase,value='Done',uvalue='zoomdone')
    widget_control,zbase,/realize
    widget_control,zoom,set_value=img
    xmanager,'mkzoom',zbase,event_handler='EITDISP_event'
end
;------------------------------------------------------------------------------
; this procedure displays images, if Movie (IDL save set, then call eit_movie,
; if Image (FITS) call eit_image
;------------------------------------------------------------------------------

pro showeit,origin=origin,v_off=v_off
common filestuff,dirspec,flist,index,list7,text6,use_lz,use_qkl,use_coll,$
       bgroup5,half
;
; List only bona fide EIT_MOVIE-compatible movies and FITS files, respectively,
; for the movie and image cases. D.M. fecit, 1996/02/25.
;
print, '%EIT_DISPLAY-D-DIRSPEC, dirspec = ' + dirspec
;
   break_file,dirspec(0),disk_log,diry,filnam
   fname=strlowcase(flist(index))
   end_template=strlen(fname)-1
   if strpos(strlowcase(dirspec(0)), 'movie') ge 0 then begin
      file_template='ems'
   endif else if strpos(strlowcase(dirspec(0)), 'ref') ge 0 or $
     strpos(strlowcase(dirspec(0)), 'quicklook') ge 0 or $
     strpos(strlowcase(dirspec(0)), 'ql') ge 0 then begin
      file_template='efr'
      end_template=18
   endif else if strpos(strlowcase(dirspec(0)), 'lz') ge 0 then begin
      file_template='efz'
      end_template=18
   endif else file_template = ''
;
   if file_template ne '' then filename=disk_log+diry+strmid(flist(index),$
          strpos(fname,file_template),end_template) else $
          filename=flist(index)
;
; 1 is the nominal "true" return from is_ss and is_fits, so let's replace
; this with some code that's just a little easier to read.
; D.M. fecit, 1996 March 10.
;
;  stat=is_ss(filename)
;  if stat eq 1 then eit_movie,filename else begin
;         stat=is_fits(filename)
;         if stat eq 1 then img=eit_image(filename,/show,v_off=46, $
;              repl = eit_dark(), dark = eit_dark())
;         else message,/continue,'File is neither a FITS or IDL Save Set'
;  endelse
;
   if is_ss(filename) then begin
      eit_movie, filename
   endif else begin
      v_off=46
      filename=strlowcase(filename)
      if strpos(filename, 'ef') eq 0 then begin
         filename = strmid(filename, 0, 18)
      end
print, filename
      stat=is_fits(filename)
      if stat ne 1 then begin
           filename=eit_file2path(filename,collapse=use_coll)
print, filename
           stat=is_fits(filename)
      endif
      if stat eq 1 then begin
         hdr=headfits(filename)
         naxis=eit_fxpar(hdr,'NAXIS')
         if naxis eq 3 then begin
           nimgs=eit_fxpar(hdr,'NAXIS3')
           comms=eit_fxpar(hdr,'COMMENT')
           start=where(strpos(comms,'BEGIN MULTIPLE') ne -1)
           out=strarr(nimgs+7)
           out(0)='Please select from the list of images below or ALL'
           out(1)='      Image numbers range from 0-'+strtrim(nimgs-1,2)
           out(3:nimgs+6)=comms(start(0):start(0)+3+nimgs)
           answer='ALL'
           xin,answer,out,status=status
           if status eq 0 then return
           if strupcase(answer(0)) eq 'ALL' and status then begin
             window,/free,xs=1024,ys=1024
             origin=readfits(filename)
             origin=alog10((origin-848)>1)
             wv=eit_fxpar(hdr,'WAV',image=0)
             sector = ['171', '195', '284', '304']
             for j_wave = 0, 3 do if strtrim(wv(0),2) eq sector(j_wave) then $
                 i_wave = j_wave
             loadct,42 + i_wave,file=getenv('coloreit')
             times=eit_fxpar(hdr,'START_TIME',image_no='all')
             times=strmid(times,11,8)
             for i=0,nimgs-1 do begin
                 put,origin(*,*,i),i+1,nimgs,/noexact,relat=0.85
                 label_image,times(i)
             endfor
           endif else begin
             if strupcase(answer(0)) eq 'ALL' then answer(0)='0'
             image_no=fix(answer(0))
             img = eit_image(filename,repl=eit_dark(),dark=eit_dark(),/show,$
                     v_off=v_off,origin=origin,image_no=image_no, /flat)
           endelse
         endif else begin
            xmg = 'The Image you selected has all missing blocks.'
            nmiss = eit_fxpar(hdr,'n_missing_blocks')
            if nmiss eq 1024 then xmessage,xmg,wait=3 else $
              img = eit_image(filename, repl = eit_dark(),half=half,dark = $
                    eit_dark(), /show, v_off=v_off,origin=origin, /flat)
         endelse
      endif else begin
         message, /continue, 'File is neither a FITS or IDL Save Set.'
stop
      end
   end
;
; end of D.M. changes, 1996 March 10.
;
end

;------------------------------------------------------------------------------
; event procedure for top level widget.
;------------------------------------------------------------------------------
PRO EITDISP_Event, Event
common filestuff,dirspec,flist,index,list7,text6,use_lz,use_qkl,use_coll,$
       bgroup5,half
common psstuff,save_dir
;
   WIDGET_CONTROL,Event.Id,GET_UVALUE=Ev

   CASE Ev OF

   'donehelp': killhelp

   'zoomdone': killzoom

   'collapse': BEGIN
       CASE Event.Value OF
       0: use_coll=0
       1: use_coll=1
          ENDCASE
              END

    'halfres': BEGIN
       CASE event.select of
       0: half = 0
       1: half = 1
         endcase
         end

   'BGROUP4': BEGIN
           if is_gsfcvms() then begin
             if index gt -1 then begin
                  fname=strlowcase(flist(index))
                  sname=strpos(fname,'efr')
                  if sname eq -1 then sname=strpos(fname,'efz')
                  if sname eq -1 then sname=strpos(fname,'ems')
                  fstop = strpos(fname,' ')
                  if fstop eq -1 then fstop = strlen(fname)
                  oname=strmid(fname,sname,fstop)
                  dname=strmid(fname,sname,18)
                  date=strmid(dname,3,4)+'/'+strmid(dname,7,2)+'/'+strmid(dname,9,2)
                  obslog,date,oname
             endif else obslog
           endif else begin
              xmg=strarr(2)
              xmg(0)='This feature is presently running only on '
              xmg(1)='the operations machines'
              xmessage,xmg,wait=5
           endelse
       END

   'BGROUP3': BEGIN
       CASE Event.Value OF
       0: BEGIN
  	    widget_control, /hourglass
	    showeit
  	    widget_control, hourglass=0
	 END
       1: BEGIN
;
; Zoom an image...only for IMAGE (FITS file). Calls procedure mkzoom
;
             break_file,dirspec(0),disk_log,diry,filnam
             fname=strlowcase(flist(index))
             tempname=strpos(fname,'efr')
             if tempname eq -1 then tempname=strpos(fname,'efz')
             if tempname ne -1 then filename=disk_log+diry+$
                 strmid(fname,tempname,18) else filename=fname
             stat=is_fits(filename)
             if stat ne 1 then begin
                 filename=eit_file2path(filename,collapse=use_coll)
                 stat=is_fits(filename)
             endif
             widget_control,/hourglass
             if stat eq 1 then mkzoom,filename $
               else message,/continue,'File is not a FITS file'
  	    widget_control, hourglass=0
          END
       2: BEGIN
;
; Displays header for IMAGE (FITS file). Calls procedure disphd
;
             break_file,dirspec(0),disk_log,diry,filnam
             fname=strlowcase(flist(index))
             tempname=strpos(fname,'efr')
             if tempname eq -1 then tempname=strpos(fname,'efz')
             if tempname ne -1 then filename=disk_log+diry+$
                 strmid(fname,tempname,18) else filename=fname
             stat=is_fits(filename)
             if stat ne 1 then begin
                 filename=eit_file2path(filename,collapse=use_coll)
                 stat=is_fits(filename)
             endif
             if stat eq 1 then disphd,filename $
               else message,/continue,'File is not a FITS file'
          END
       3: BEGIN
             while !d.window ge 0 do wdelete, !d.window
	    showeit,origin=origin,v_off=v_off
             rdpix,origin,0,-v_off
             origin=0
          END
       4: XLOADCT,file=getenv('coloreit')
       5: BEGIN
             break_file,dirspec(0),disk_log,diry,filnam
             fname=strlowcase(flist(index))
             tempname=strpos(fname,'efr')
             if tempname eq -1 then tempname=strpos(fname,'efz')
             filename=disk_log+diry+strmid(fname,tempname,18)
             stat=is_fits(filename)
             if stat ne 1 then begin
                 filename=eit_file2path(filename,collapse=use_coll)
                 stat=is_fits(filename)
             endif
             reallist=['Select Printer','SOHO_COLOR2',$
                'EAF-color1','SOHO_COLOR3','Save to a disk file only']
             printlist=['Select Printer','SOHO_COLOR2 (dye sub paper)',$
                'EAF-color1 (dye sub paper)','SOHO_COLOR3 (plain paper)',$
                'Save to a disk file only']
             printer=reallist(qmenu(printlist,init=1,title=0))
             save_dir=0
             if printer eq 'Save to a disk file only' then begin
                 printer=0
                 save_psdir
             endif
             if stat eq 1 then eit_dump,filename,/post,printer=printer, $
               outdir=save_dir else message,/continue,'File is not a FITS file'
          END
       6: while !d.window ge 0 do wdelete, !d.window
       7: WIDGET_CONTROL, /DESTROY, event.top
       8: helpout
       ELSE: Message,/continue,'Unknown button pressed'
       ENDCASE
       END
   'BGROUP5': BEGIN
       CASE Event.Value OF
           0: begin
                dirspec=getenv('MOVIE_DIR')          ;choose IDL movies
                flist=find_file(concat_dir(dirspec(0),'ems*.*'))
                widget_control, text6, set_value=dirspec
                widget_control, list7,set_value=flist
              end
           1: begin
		yeardir = strmid(anytim2utc(!stime, /ecs), 0, 4)
                dirspec=getenv('MOVIE_ARCHIVE')          ;choose IDL movies
		; A quick check to see if VMS - e einfalt - 2003/05/05
                if !version.os ne 'vms' then dirspec=dirspec(0)+yeardir+'/' $
					else dirspec=dirspec(0)+'['+yeardir+']' 
                flist=find_file(concat_dir(dirspec(0),'ems*.*'))
                widget_control, text6, set_value=dirspec
                break_file,flist,dum,dum,movnames,ext
                widget_control, list7,set_value=movnames+ext
              end
           ELSE: Message,/continue,'Unknown button pressed'
       ENDCASE
       END


;
; Added year droplist to select the year subdirectory in new movie archive
; C.A. Young, 2003 May 2
    'yrform1': begin
              year_now = strmid(anytim2utc(!stime, /ecs), 0, 4)
              current_year = fix(year_now)
              yrforml = strtrim(string(1996 + indgen(current_year - 1995)), 2)
              yeardir = yrforml(event.index)
              ; dirspec=getenv('MOVIE_ARCHIVE')+yeardir+'/'   einfalt - 2003/05/05
	      ; A quick check to see if VMS - e einfalt - 2003/05/05
              dirspec=getenv('MOVIE_ARCHIVE')          ;choose IDL archived movies
              if !version.os ne 'vms' then dirspec=dirspec(0)+yeardir+'/' $
				      else dirspec=dirspec(0)+'['+yeardir+']' 
              widget_control,text6,set_value=dirspec
              flist=find_file(concat_dir(dirspec(0),'ems*.*'))
              break_file,flist,dum,dum,movnames,ext
              widget_control,list7,set_value=flist
             end
;end addition C.A. Young, 2003 May 2

   'dateit':BEGIN
               widget_control, event.id, get_value=date
               if strpos(strupcase(date(0)),'ALL') ge 0 then date=!stime
               if strpos(strlowcase(date(0)),"/y") ge 0 then $
	           date   = doy2utc(utc2doy(anytim2utc(!stime))-1) $		
               else if strpos(strlowcase(date(0)),"y=") ge 0 then begin
	           back = (str_sep(date(0),"="))(1)
	           date   = doy2utc(utc2doy(anytim2utc(!stime))-back)		
               endif
               date=strmid(anytim2utc(date,/ecs),0,10)
               fnames=''
               entry=eit_catrd(date,/raw,filename=fnames,lz=use_lz)
               if use_lz then file_template='efz' else if use_qkl then $
                      file_template='efr'
               if datatype(entry) ne 'STC' then begin
                  xmg=strarr(5)
                  xmg(0)='The catalog search program did not find any images'
                  xmg(1)='on that day. If LZ was selected please check to see'
                  xmg(2)='if the processing is current.'
                  xmg(3)=' '
                  xmg(4)='Please select another date'
                  xmessage,xmg,wait=7
                  return
               endif
               version_no = (ishft(entry.version,-4) and '0f'x) + $
                            (entry.version and '0f'x)/10.
               new_v = where(version_no ge 2.0)
               exptime = float(entry.exp_time)
               if new_v(0) ne -1 then exptime(new_v) = entry(new_v).exp_time/10.
;              time_str = strtrim(exptime,2)
               time_str = strtrim(string(exptime, format = '$(f6.1)'), 2)
               waves=fix(entry.wave(0))+170
               nxstr=strtrim(fix(entry.nx)*32,2)
               nystr=strtrim(fix(entry.ny)*32,2)
               nxsum=strtrim(fix(entry.nx_sum>1),2)
               nysum=strtrim(fix(entry.ny_sum>1),2)
               filter = replicate('?      ', n_elements(entry.filter))
               filt_str = ['Al + 1 ','Blk Est','Clear  ','Blk Wst','Al + 2 ']
               w_filter = where(entry.filter ge 0 and entry.filter le 4, n_filt)
               if n_filt gt 0 then filter(w_filter)=filt_str(entry(w_filter).filter)
               sec_filt = strtrim(fix(waves),2) + '::' + filter
               flist=fnames+'     '+sec_filt
               flist=flist+'   (' +nxstr+',' +nystr+' / '+nxsum+'x'+nysum+')'
               flist=flist+'    ' + time_str + ' s'
               multim=replicate('',n_elements(entry.n_repeat))
               w_multim=where(entry.n_repeat gt 0,n_mult)
               if n_mult gt 0 then multim(w_multim)=$
                   strtrim(entry(w_multim).n_repeat,2)+'-img /'+ $
                    strtrim(fix(entry(w_multim).n_wave),2)+'-wvs'
               flist=flist+'  '+multim
               flist=reverse(flist)
; added call to eit_file2path for directory name
               use_gavroc=0
               if !version.os eq 'vms' then begin
                   machine=strlowcase(getenv('UCX$INET_HOST'))
                   if machine eq 'gavroche' or machine eq 'xanado' $
                      then use_gavroc=1
               endif
               dirspec=eit_file2path(fnames(0),lz=use_lz,gavroc=use_gavroc,$
                        collapse=use_coll)
               pos=strpos(dirspec,file_template)
               dirspec=strmid(dirspec,0,pos)
;
               pos=strpos(fnames(0),'.')
               dirspec=dirspec(0)+'*'+strmid(fnames(0),pos-4,4)+'*'
               widget_control, text6,set_value=dirspec(0)
               widget_control, list7,set_value=flist
               widget_control, bgroup5, set_button = 0
            END

   'TEXT6': begin                 ;get input directory
              widget_control, event.id, get_value=dirspec
;
; List only bona fide EIT_MOVIE-compatible movies and FITS files, respectively,
; for the movie and image cases. D.M. fecit, 1996/02/25.
;
print, '%EIT_DISPLAY-D-DIRSPEC, dirspec = ' + dirspec
;
   break_file,dirspec(0),disk_log,diry,filnam
   if strpos(strlowcase(dirspec(0)), 'movie') ge 0 then begin
      file_template = 'ems'
   endif else if strpos(strlowcase(dirspec(0)), 'ref') ge 0 or $
     strpos(strlowcase(dirspec(0)), 'quicklook') ge 0 or $
     strpos(strlowcase(dirspec(0)), 'ql') ge 0 then begin
      file_template='efr'
   endif else if strpos(strlowcase(dirspec(0)), 'lz') ge 0 then begin
      file_template='efz'
   endif else file_template = ''
;
              flist=find_file(disk_log+diry+file_template+filnam+'*.*')
;
; End of D.M. changes, 1996/02/25
;
              if flist(0) ne '' and file_template ne 'ems' then begin
                  flist=reverse(flist)
                  if file_template ne '' then flist=strmid(flist,$
                     strpos(flist(0),file_template),strlen(flist(0)))
              endif
              widget_control, list7, set_value=flist, ysize = 12
              return
            end
   'LIST7': begin
              index=event.index     ;get index for file choice
              if event.clicks eq 2 then begin
		widget_control, /hourglass
		showeit
		widget_control, hourglass=0
	     endif
            end
   'SDIR' : begin
                widget_control, event.id, get_value=save_dir
                killhelp
            end
   ENDCASE
END

;---------------------------------------------------------------------------
; This procedure sets up the main widget interface as well as initial
; values. Call is simply EIT_DISPLAY
;---------------------------------------------------------------------------
PRO eit_display, GROUP=Group
common filestuff,dirspec,flist,index,list7,text6,use_lz,use_qkl,use_coll,$
       bgroup5,half
;
   defsysv,'!image',exist=ok
   if not ok then begin
      imagelib
      devicelib
   endif
   use_qkl=1 & use_lz=0 & use_coll=0
;
; dirspec changed back to REF_DIR with the amazing resurrection of Lazarus J.
; EIT, 1998 October 14.
;
; dirspec=getenv('MOVIE_DIR')
  dirspec=getenv('REF_DIR')
;
   if dirspec(0) eq '' then dirspec=getenv('REF_DIR')
   if dirspec(0) eq '' then dirspec=getenv('EIT_QKL')+ $
         strmid(anytim2utc(!stime,/ecs),0,10)+'/'
   if strpos(strlowcase(dirspec(0)), 'movie') ge 0 then begin
      file_template = 'ems'
   endif else if strpos(strlowcase(dirspec(0)), 'ref') ge 0 or $
     strpos(strlowcase(dirspec(0)), 'quicklook') ge 0 then begin
      file_template = 'efr'
   endif else file_template = ''
   IF N_ELEMENTS(Group) EQ 0 THEN GROUP=0

;   top level base
   EITDISP = WIDGET_BASE(GROUP_LEADER=Group, COLUMN=1, MAP=1, $
       TITLE='EIT Display System', UVALUE='EITDISP')

; button group = actions
   Btns459 = [ 'Display','Zoom', 'Show Header','RDPIX','XLOADCT',$
         'PRINT','Delete All Windows','Done','Help' ]
   BGROUP3 = CW_BGROUP( EITDISP, Btns459, ROW=1, UVALUE='BGROUP3')
   Btns_ob = [ 'Observing Log']
   BGROUP4 = CW_BGROUP( EITDISP, Btns_ob, ROW=1, UVALUE='BGROUP4')

; label widget
   d4 = WIDGET_LABEL( EITDISP, /align_left, UVALUE='d4', VALUE='  ')
   LABEL4 = WIDGET_LABEL( EITDISP, /align_left, $
       UVALUE='LABEL4', VALUE='Enter Date for Single Files or Select Movie Dir.')

;child base for 2 columns
   child=WIDGET_BASE(EITDISP,COLUMN=4)

;date label and input text widget
   dateit = WIDGET_TEXT( child,VALUE=anytim2utc(!stime,/date,/vms), $
       EDITABLE=1, UVALUE='dateit',YSIZE=1,xsize=15)

;button group - file formats
   Btns601 = [ 'MOVIE_DIR (IDL Save Sets)','MOVIE_ARCHIVE (IDL Save Sets)']
    BGROUP5 = CW_BGROUP( child, Btns601, EXCLUSIVE=1, COLUMN=1, $
       UVALUE='BGROUP5')

;data directory format, standard or collapsed
;button group - file formats
   Btns2 = [ 'Standard Tree','Collapsed Tree']
   BGROUP6 = CW_BGROUP( child, Btns2, EXCLUSIVE=1, COLUMN=2, $
       LABEL_TOP='Data Tree Organization', UVALUE='collapse')

   half = 0
   fbase= widget_base(child,/nonexclusive)
   btns3 = widget_button(fbase, value='Half Res', uvalue='halfres')


;
; Added year droplist to select the year subdirectory in new movie archive
; C.A. Young, 2003 May 2
;
   child=WIDGET_BASE(EITDISP,COLUMN=1)
   year_now = strmid(anytim2utc(!stime, /ecs), 0, 4)                 
   current_year = fix(year_now)                                      
   yrforml = strtrim(string(1996 + indgen(current_year - 1995)), 2)
   yrform1 = widget_droplist(child, value = yrforml,$
      title = 'Select Movie Archive Year:', uvalue = 'yrform1')
;
;end addition

;label widget
   LABEL12 = WIDGET_LABEL( EITDISP, UVALUE='LABEL12', $
       VALUE='Directory Name')

;input text widget for directories
   TextVal704 =dirspec
   TEXT6 = WIDGET_TEXT( EITDISP,VALUE=TextVal704, $
       EDITABLE=1, UVALUE='TEXT6',YSIZE=1)

;label widget - for file listing
   LABEL16 = WIDGET_LABEL( EITDISP, UVALUE='LABEL16', $
       VALUE='List of Files')

;list widget - displays files
   flist = find_file(dirspec+file_template+'*.*')
   if strpos(strupcase(dirspec(0)),'MOVIE') eq -1 and flist(0) ne '' then begin
        flist=reverse(flist)
         
flist=strmid(flist,strpos(flist(0),file_template),strlen(flist(0)))
   endif
   ys=n_elements(flist)
   LIST7 = WIDGET_LIST( EITDISP,VALUE=flist+string(replicate(32b,20)), $
       UVALUE='LIST7', YSIZE = 12)

;realize widget and hand off to xmanager
   WIDGET_CONTROL, EITDISP, /REALIZE
   XMANAGER, 'EITDISP', EITDISP
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:45:00 2007- F. Auchère