;+ ; NAME: ; smei_frm_summary ; PURPOSE: ; Plots time series for various basic parameters in SMEI data frames ; CATEGORY: ; camera/idl/frm ; CALLING SEQUENCE: PRO smei_frm_summary, frame, printer=printer, zbuffer=zbuffer, $ destination=destination, _extra=_extra, $ nfill_control=nfill_control, nbad_control=nbad_control, $ hdr=hdr, silent=silent ; INPUTS: ; frame array[1], or array[2]; type: time structure ; begin and end time for time range to be plotted. ; If only a start time is given then the end time is taken ; to be the start time, plus one day. ; OPTIONAL INPUT PARAMETERS: ; source=source ; destination=destination ; camera=camera ; OUTPUTS: ; (to png file) ; OPTIONAL OUTPUT PARAMETERS: ; INCLUDE: @compile_opt.pro ; On error, return to caller ; EXTERNAL: ; smei_frm_hdr__define ; CALLS: ; InitVar, IsType, CheckDir, destroyvar, jpl_phase ; TimeUnit, TimeOp, TimeSet, TimeGet, TimeScale ; TimeLimits, BadValue, smei_frm_where, set_page, PlotCurve, TimeXAxis ; get_page, smei_getfile, smei_frm_track, jpl_body, TimeSystem ; COMMON BLOCKS: ; PROCEDURE: ; TO DO: ; - Dark current subtraction does not take slope from row to row into account ; (especially important for camera three) ; - Definition of SAA needs improvement ; MODIFICATION HISTORY: ; APR-2003, Paul Hick (UCSD/CASS; pphick@ucsd.edu) ;- InitVar, silent , 0 InitVar, printer , /key zbuffer = 1-printer IF IsType(destination, /defined) THEN $ IF NOT CheckDir(destination) THEN $ destroyvar, destination ff = smei_getfile(frame, tt=tt, count=count, _extra=_extra) IF count EQ 0 THEN BEGIN message, /info, 'no frames found' RETURN ENDIF hdr = replicate({smei_frm_hdr}, count) chdr = strarr(count) frm = -1 loc = smei_frm_track(frm, count, nfill_control=nfill_control, nbad_control=nbad_control) WHILE frm LT count DO BEGIN frm_in = frm loc = smei_frm_track(frm, ff=ff[frm], hdr=tmp, status=status, $ nfill_control=nfill_control, nbad_control=nbad_control, silent=silent) IF loc NE -1 THEN BEGIN hdr [loc] = tmp chdr[loc] = status ENDIF ;IF loc NE -1 THEN print, ff[loc],smei_property(hdr[loc],/time) ENDWHILE ; Includes Sun, planets and Moon nbody = jpl_body(/moon)+1 jpl_list = indgen(nbody) pos_bodies = bytarr(nbody, count) smei_frm_where, hdr, sc_loc=pos_coriolis, pointing=pos_camera, /degrees, $ jpl_list=jpl_list, inside=tmp, name=name, nobject=nobject IF nobject NE 0 THEN pos_bodies[jpl_body(name),*] = tmp ;pos_coriolis = replicate(BadValue(0d0),3,count) ;pos_camera = replicate(BadValue(0d0),3,count) ;pos_bodies = bytarr(nbody, count) ;FOR frm=0,count-1 DO BEGIN ; smei_frm_where, hdr[frm], sc_loc=tmp1, cam_loc=tmp2, /degrees, $ ; jpl_list=jpl_list, inside=tmp3, name=tmp4 ; ; pos_coriolis[*,frm] = tmp1 ; pos_camera [*,frm] = tmp2 ; if IsType(tmp4, /defined) then pos_bodies[jpl_body(tmp4),frm] = tmp3 ; ;ENDFOR ; Estimated position of SAA (needs improvement) pos_saa = sphere_distance( [-45,-30], pos_coriolis[0:1,*], /degrees) le 25 ped = smei_property(hdr,/pedestal) drk = smei_property(hdr,/dark_current) sqr = smei_property(hdr,/squares) pix = smei_property(hdr,/centerpix) whatis, ped, drk, sqr, pix CASE IsTime(frame) OF 0: trange = TimeLimits(tt , /range) 1: trange = TimeLimits(frame, /range) ENDCASE FOR icam=0,2 DO BEGIN pcam = where( smei_property(hdr,/camera) eq icam+1, ncam ) IF ncam GT 0 THEN BEGIN openw, /get_lun, iu, filepath(root=getenv('TUB'), $ 'c'+strcompress(icam+1,/rem)+'_'+ $ strjoin(TimeGet( trange, /_ydoy, upto=TimeUnit(/hour)),'_')+'.txt') tmp = where( 1-finite(ped[pcam]) or 1-finite(drk[0,pcam]), n) printf, iu, 'rejected', n, ' out of', ncam, ' frames' IF n GT 0 THEN BEGIN pcam = pcam[tmp] ; All rejected frames ; Write names of frames with bad pedestals and/or dark current ; Skip bad frames inside SAA or with Moon inside fov. tmp = where(1-pos_saa[pcam] and 1-pos_bodies[jpl_body(/moon),pcam], n) printf, iu, strcompress(n,/rem)+' rejected frames not affected by SAA or Moon' IF n GT 0 THEN BEGIN pcam = pcam[tmp] tmp = pos_bodies[jpl_body(/venus),pcam] ; Venus in fov FOR i=0L,n-1 DO printf, iu, chdr[pcam[i]]+(['',' Venus'])[tmp[i]] ENDIF ENDIF free_lun, iu ENDIF ENDFOR destroyvar, chdr chars = 2 psym = 3 black = 0 darkgreen = 2 green = 16 lightgreen = 32 darkblue = 96 purple = 112 pink = 128 red = 192 pedcolor = red drkcolor = darkblue sqrcolor = purple pixcolor = darkgreen modcolor = red latcolor = black lngcolor = darkblue tiltcolor = red uhour = TimeUnit(/hour) tbig = TimeOp(/subtract,trange[1],trange[0],uhour) tbig = TimeOp(/add, trange, TimeSet(hour=0.05d0*tbig*[-1,1]) ) xmargin = [7,7] FOR icam=0,2 DO BEGIN pcam = where( smei_property(hdr,/camera) EQ icam+1, ncam ) CASE ncam NE 0 OF 0: message, /info, 'no data for camera'+strcompress(icam+1) 1: BEGIN tcam = tt[pcam] set_page, xysize=[800,750], printer=printer, zbuffer=zbuffer, ctable=12 !p.multi = [0,1,6] ;=============== ; Coriolis spacecraft TimeXAxis, tbig, uhour, /exact, /noxtitle, ymargin=[0,2.5], chars=chars, upto=upto, xmargin=xmargin tmp = convert_coord( !x.crange, !y.crange, /to_normal) xtop = tmp[0,0:1] ytop = tmp[1, 1]+0.005 PlotCurve, tcam, smei_property(hdr[pcam],/mode), psym=psym, /oplot, /newyaxis, $ chars=chars, ytitle='Mode', ystyle=1, yrange=[-0.5,2.5], $ ytickv=[0,1,2], yticks=3, color=modcolor, /silent PlotCurve, tcam, pos_coriolis[1,pcam], psym=psym, /oplot, /newyaxis, $ yaxis=0, chars=chars, ystyle=1, yrange=190*[-1,1], $ ytickv=90*[-1,0,1], yticks=3, color=latcolor, ytitle='Coriolis', /silent PlotCurve, tcam, pos_coriolis[0,pcam], psym=psym, /oplot, $ chars=chars, color=lngcolor, /silent inside = pos_saa[pcam] tmp = where( inside ) WHILE tmp[0] NE -1 DO BEGIN ib = tmp[0] ie = (where(1-inside[ib:*]))[0] ie = ([ib+ie,ncam]-1)[ie eq -1] tmp = TimeScale(tcam[[ib,ie]]) oplot, [tmp[0],tmp[1],tmp[1],tmp[0],tmp[0]], -190+20*[0,0,1,1,0], color=green inside[ib:ie] = 0B tmp = where( inside ) ENDWHILE ;================ ; Pedestal yy = ped[pcam] yy_mean = mean(yy, /nan) if total(finite(yy)) gt 1 then yy_stdev = stddev(yy, /nan) else yy_stdev = BadValue(yy) message, /info, 'Cam'+strcompress(icam+1)+ $ ' pedestal'+strcompress(yy_mean)+' ('+strcompress(yy_stdev)+')' yrange = [0,7] ytickv = [1,3,5] yticks = n_elements(ytickv) offset = floor(min(yy,/nan)/1.0)*1 ytitle = 'Pedestal' if offset ne 0 then ytitle = ytitle+'-'+strcompress(offset,/rem) TimeXAxis, /noxtitle, ymargin=[0,0], chars=chars, xmargin=xmargin PlotCurve, tcam, yy-offset, psym=psym, /oplot, /newyaxis, $ chars=chars, ytitle=ytitle, ystyle=1, yrange=yrange, $ ytickv=ytickv, yticks=yticks, color=pedcolor, /noclip, /silent ;================ ; Dark current yy = drk[0,pcam] yy_mean = mean(yy, /nan) IF total(finite(yy)) GT 1 THEN yy_stdev = stddev(yy, /nan) ELSE yy_stdev = BadValue(yy) message, /info, 'Cam'+strcompress(icam+1)+ $ ' dark current'+strcompress(yy_mean)+' ('+strcompress(yy_stdev)+')' CASE icam+1 OF 3: begin yrange = [0,8] ytickv = [2,4,6] END ELSE: BEGIN yrange = [0,4] ytickv = [1,2,3] END ENDCASE yticks = n_elements(ytickv) offset = floor(min(yy,/nan)/1.0)*1 ytitle = 'Dark Current' if offset ne 0 then ytitle = ytitle+'-'+strcompress(offset,/rem) TimeXAxis, /noxtitle, ymargin=[0,0], chars=chars, xmargin=xmargin PlotCurve, tcam, yy-offset, psym=psym, /oplot, /newyaxis, $ chars=chars, ytitle=ytitle, ystyle=1, yrange=yrange, $ ytickv=ytickv, yticks=yticks, color=drkcolor, /noclip, /silent ;================ ; Squares left and right yrange = [0,8] ytickv = [2,4,6] yticks = n_elements(ytickv) offset = floor(min(sqr[pcam],/nan)/1.0)*1 ytitle = 'Squares' if offset ne 0 then ytitle = ytitle+'-'+strcompress(offset,/rem) TimeXAxis, /noxtitle, ymargin=[0,0], chars=chars, xmargin=xmargin PlotCurve, tcam, sqr[pcam]-offset, psym=psym, /oplot, /newyaxis, $ chars=chars, ytitle=ytitle, ystyle=1, yrange=yrange, $ ytickv=ytickv, yticks=yticks, color=sqrcolor, /silent ; Single center group CASE icam+1 OF 3: begin yrange = [ 0,40] ytickv = [10,20,30] END ELSE: BEGIN yrange = [ 0,28] ytickv = [ 7,14,21] END ENDCASE yticks = n_elements(ytickv) offset = floor(min(pix[pcam],/nan)/1.0)*1 ytitle = 'Center' if offset ne 0 then ytitle = ytitle+'-'+strcompress(offset,/rem) TimeXAxis, /noxtitle, ymargin=[0,0], chars=chars, xmargin=xmargin PlotCurve, tcam, pix[pcam]-offset, psym=psym, /oplot, /newyaxis, $ chars=chars, ytitle=ytitle, ystyle=1, yrange=yrange, $ ytickv=ytickv, yticks=yticks, color=pixcolor, /silent ;================ ; Bodies and camera pointing TimeXAxis, /noxtitle, ymargin=[2,0], chars=chars, xmargin=xmargin PlotCurve, TimeLimits(tt[pcam],/range), [0,nbody+3], psym=psym, /oplot, /newyaxis, $ chars=chars, ytitle='Bodies', $ ystyle=1, yrange=[0,nbody+4], ytickn=[' ',' '], yticks=1, color=pedcolor, /silent yy = 0 FOR ibody=0,nbody-1 DO BEGIN inside = reform(pos_bodies[ibody,pcam]) tmp = where( inside ) IF tmp[0] NE -1 THEN BEGIN yy = yy+1.2 xyouts, !x.crange[0], yy, ' '+strmid(jpl_body(ibody),0,4) ENDIF WHILE tmp[0] NE -1 DO BEGIN ib = tmp[0] ie = (where(1-inside[ib:*]))[0] ie = ([ib+ie,ncam]-1)[ie eq -1] tmp = TimeScale(tcam[[ib,ie]]) oplot, [tmp[0],tmp[1],tmp[1],tmp[0],tmp[0]], yy+[0,0,1,1,0], color=green IF jpl_body(ibody) EQ 'Moon' THEN BEGIN tcntr = TimeLimits(tcam[[ib,ie]],/mid) phase = jpl_phase(tcntr,/degrees) tcntr = 0.5*(tmp[0]+tmp[1]) dtmp = tmp[1]-tmp[0] tcntr = tcntr-phase/180.0*dtmp tmp = [ (tcntr-0.5*dtmp) > tmp[0], (tcntr+0.5*dtmp) < tmp[1] ] IF tmp[0] LT tmp[1] THEN $ polyfill, [tmp[0],tmp[1],tmp[1],tmp[0],tmp[0]], yy+[0,0,1,1,0], color=green ENDIF inside[ib:ie] = 0B tmp = where( inside ) ENDWHILE ENDFOR PlotCurve, tcam, pos_camera[1,pcam], psym=psym, /oplot, /newyaxis, $ yaxis=0, chars=chars, ystyle=1, yrange=190*[-1,1], $ ytickv=90*[-1,0,1], yticks=3, color=latcolor, $ ytitle='Camera Pntg', /silent PlotCurve, tcam, AngleRange(pos_camera[0,pcam],/pi,/deg), $ psym=psym, /oplot, chars=chars, color=lngcolor, /silent PlotCurve, tcam, pos_camera[2,pcam], psym=psym, /oplot, $ chars=chars, color=tiltcolor, /silent ; Start time at top-left of page xyouts, /norm, xtop[0], ytop, chars=0.8*chars, $ TimeGet(trange[0], /ymd, upto=upto-(TimeGet(trange[0],upto,/scalar) EQ 0))+ $ ' Doy '+string(TimeGet(trange[0],/day), format='(I3.3)')+ $ ' Cam'+strcompress(icam+1)+' '+strcompress(ncam)+' frames' ; Print time at top-right of page (with reduced charsize) xyouts, /norm, xtop[1], ytop, align=1.0, chars=0.5*chars, $ TimeGet(TimeSystem(/silent), /ymd, upto=TimeUnit(/minute)) IF IsType(destination, /defined) THEN $ img_file = filepath(root=destination, 'c'+strcompress(icam+1,/rem)+'_'+ $ strjoin(TimeGet( trange, /_ydoy, upto=upto),'_')+'.png') get_page, img_file, printer=printer, zbuffer=zbuffer, /new END ENDCASE ENDFOR !p.multi = 0 RETURN & END