;+ ; NAME: ; smei_hdr_plot ; PURPOSE: ; Plots time series for various basic parameters in SMEI data frames ; CATEGORY: ; camera/idl/frm ; CALLING SEQUENCE: PRO smei_hdr_plot, tt , $ destination = destination , $ camera = camera , $ silent = silent , $ printer = printer , $ remote = remote , $ _extra = _extra ; INPUTS: ; tt array[2]; type: time structure ; time range to be updated ; OPTIONAL INPUT PARAMETERS: ; destination=destination ; remote=remote scalar; type: string; default: none ; if present, is combined with destination to build ; the destination as : ; (usually "remote" is set to the computer hosting ; the header database when this routine is executed ; on another computer) ; 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, smei_hdr_get, jpl_phase ; TimeUnit, TimeOp, TimeSet, TimeGet, TimeScale ; TimeLimits, BadValue, smei_frm_where, set_page, PlotCurve, TimeXAxis ; get_page, jpl_body, TimeSystem, sphere_distance ; PROCEDURE: ; - Definition of SAA needs improvement ; MODIFICATION HISTORY: ; SEP-2005, Paul Hick (UCSD/CASS) ; OCT-2007, Paul Hick (UCSD/CASS; pphick@ucsd.edu) ; Added PlotCurve calls to shade periods with ; bad quaternions. ;- InitVar, destination, getenv('TUB') InitVar, camera , [1,2,3] InitVar, silent , 0 IF NOT CheckDir(destination) THEN BEGIN message, /info, 'destination does not exist, '+hide_env(destination) RETURN ENDIF CASE 1 OF IsType(tt, /undefined): BEGIN message, /info, 'no time range specified' RETURN END IsType(tt,/string): tt = TimeSet(tt) ELSE: ENDCASE one_day = n_elements(tt) EQ 1 AND TimeGet(tt[0],/fotime,/day,/full,/scalar) EQ 0 CASE n_elements(tt) EQ 1 OF 0: trange = tt[0:1] 1: trange = [tt, TimeOp(/add, tt, TimeSet(/diff,day=1))] ENDCASE uday = TimeUnit(/day) uhour = TimeUnit(/hour) usec = TimeUnit(/sec) InitVar, printer , /key zbuffer = 1-printer chars = 2 psym = 3 black = 0 darkgreen = 2 green = 16 lightgreen = 32 darkblue = 96 purple = 112 pink = 128 red = 192 grey = 231 pedcolor = red drkcolor = darkblue sqrcolor = purple pixcolor = darkgreen modcolor = red ffecolor = green shutcolor = darkblue latcolor = black lngcolor = darkblue tiltcolor = red saacolor = green badqcolor = grey xmargin = [7,7] tbig = TimeOp(/subtract,trange[1],trange[0],uhour) tbig = TimeOp(/add, trange, TimeSet(hour=0.05d0*tbig*[-1,1]) ) torb = TimeGet(/smei,tbig) torb = smei_orbit_get(torb,/number)+[1,0] norb = torb[1]-torb[0]+1 orbs = torb[0]+lindgen(norb) ; Orbits starting in trange torb = TimeSet(smei=orbs) orbs5 = orbs[where((orbs[0:norb-2] mod 5) EQ 0,norb5)] ; Multiple of 5 torb5 = TimeSet(smei=smei_orbit_set(orbs5,0.5d0)) orbs5 = strcompress(orbs5,/rem) FOR icam=0,n_elements(camera)-1 DO BEGIN cam = camera[icam] smei_hdr_get, trange, camera=cam, silent=silent, _extra=_extra, hdr=hdr, count=count, dbname=dbname IF count EQ 0 THEN BEGIN message, /info, 'no frms for cam'+strcompress(cam)+ $ ' in '+strjoin(TimeGet(trange,/_ydoy,upto=usec), ' - ') break ENDIF dbname = 'DB'+strcompress(round((sfloat(hide_env(dbname[0])))[0]),/rem) bad_data = smei_property(hdr[0],/bad_data) ; Bad data flag (-999.0) version = smei_property(hdr[0],/version) message, /info, strcompress(count,/rem)+' frms for cam'+strcompress(cam)+ $ ' in '+strjoin(TimeGet(trange,/_ydoy,upto=usec), ' - ') time = smei_property(hdr,/time) mode = smei_property(hdr,/mode) flat = smei_property(hdr,/onboard_ff_enabled) shut = smei_property(hdr,/shutter_open) IF one_day THEN BEGIN cal_patt = smei_property(hdr,/cal_pattern) cal_patt = cal_patt[uniq(cal_patt,sort(cal_patt))] i = where( TimeGet(smei_filename(cal_patt) ,/_ydoy,upto=uday) EQ $ TimeGet(trange[0] ,/_ydoy,upto=uday,/scalar), $ ni, complement=j, ncomplement=nj ) FOR k=0,ni-1 DO message, /info, 'same-day calibration pattern, '+cal_patt[i[k]] FOR k=0,nj-1 DO BEGIN tmp = cal_patt[j[k]] CASE strlen(strtrim(tmp)) EQ 0 OF 0: message, /info, 'other-day calibration pattern, '+tmp 1: message, /info, 'some data not run through smei_base yet' ENDCASE ENDFOR CASE ni EQ 0 OF 0: cal_patt = cal_patt[i] 1: destroyvar, cal_patt ENDCASE ENDIF badq = smei_property(hdr,/bad_quat) shade_badq = total(badq) NE 0 ; 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 ; Estimated position of SAA (needs improvement) pos_saa = sphere_distance( [-45,-30], pos_coriolis[0:1,*], /degrees) LE 25 ; Make plots 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 ; Shade area with bad quaternions IF shade_badq THEN PlotCurve, time, badq, /bar, shade=grey, /oplot, /newyaxis, ystyle=4, /noline PlotCurve, time, 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 ; Plot thick line at location of calibration pattern IF IsType(cal_patt,/defined) THEN $ FOR i=0,n_elements(cal_patt)-1 DO $ PlotCurve, replicate(smei_filename(cal_patt[i]),2), [-0.5,2.5], /oplot, thick=2, /silent ; Mark orbit start with vertical dashed line and print orbit number ; centered in the orbit. FOR i=0,norb -1 DO PlotCurve, replicate(torb[i],2), [-0.5,2.5], /oplot, linestyle=1, /silent tmp = !y.crange[1]-0.1*(!y.crange[1]-!y.crange[0]) FOR i=0,norb5-1 DO xyouts, TimeScale(torb5[i]), tmp, orbs5[i], chars=0.5*chars, align=0.5 PlotCurve, time, flat+0.05, psym=psym, /oplot, color=ffecolor, /silent PlotCurve, time, shut+0.12, psym=psym, /oplot, color=shutcolor, /silent PlotCurve, time, pos_coriolis[1,*], 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, time, pos_coriolis[0,*], psym=psym, /oplot, $ chars=chars, color=lngcolor, /silent inside = pos_saa tmp = where( inside ) WHILE tmp[0] NE -1 DO BEGIN ib = tmp[0] ie = (where(1-inside[ib:*]))[0] ie = ([ib+ie,count]-1)[ie eq -1] tmp = TimeScale(time[[ib,ie]]) oplot, [tmp[0],tmp[1],tmp[1],tmp[0],tmp[0]], -190+20*[0,0,1,1,0], color=saacolor inside[ib:ie] = 0 tmp = where( inside ) ENDWHILE tmp = where( smei_property(hdr,/base_done), complement=base_notdone) base_ok = where( smei_property(hdr,/base_ok ), complement=base_notok ) ;================ ; Pedestal yy = smei_property(hdr,/pedestal) IF base_notdone[0] NE -1 THEN yy[base_notdone] = BadValue(yy) ; Eliminate frames with no ped/dark current available yet bad = where(yy EQ bad_data) ; Eliminate frames with bad ped/dark current IF bad[0] NE -1 THEN yy[bad] = BadValue(yy) yy_mean = mean(yy, /nan) IF total(finite(yy)) GT 1 THEN yy_stdev = stddev(yy, /nan) ELSE yy_stdev = BadValue(yy) message, /info, 'Camera'+strcompress(cam)+ $ ' pedestal'+strcompress(yy_mean)+' ('+strcompress(yy_stdev,/rem)+')' CASE cam OF 1: BEGIN yrange = [0,7] ytickv = [1,3,5] END 2: BEGIN yrange = [0,15] ytickv = [4,8,12] END 3: BEGIN yrange = [0,7] ytickv = [1,3,5] END ENDCASE yticks = n_elements(ytickv) ;offset = floor(min(yy,/nan)/1.0)*1 CASE base_ok[0] EQ -1 OF 0: offset = floor(min(yy[base_ok],/nan)/1.0)*1 1: offset = floor(min(yy,/nan)/1.0)*1 ENDCASE ytitle = 'Pedestal' IF offset NE 0 THEN ytitle = ytitle+'-'+strcompress(offset,/rem) TimeXAxis, /noxtitle, ymargin=[0,0], chars=chars, xmargin=xmargin IF shade_badq THEN PlotCurve, time, badq, /bar, shade=grey, /oplot, /newyaxis, ystyle=4, /noline FOR i=0,norb-1 DO PlotCurve, torb[[i,i]], [0,1], /oplot, /newyaxis, ystyle=4, linestyle=1, /silent PlotCurve, time, yy-offset, base_ok, psym=psym, /oplot, /newyaxis, $ chars=chars, ytitle=ytitle, ystyle=1, yrange=yrange, $ ytickv=ytickv, yticks=yticks, /noclip, /silent, $ /changecolor, color=[pedcolor,saacolor] ;================ ; Dark current yy = smei_property(hdr,/dark_current) IF base_notdone[0] NE -1 THEN yy[base_notdone] = BadValue(yy) bad = where(yy EQ bad_data) IF bad[0] NE -1 THEN yy[bad] = BadValue(yy) yy_mean = mean(yy, /nan) IF total(finite(yy)) GT 1 THEN yy_stdev = stddev(yy, /nan) ELSE yy_stdev = BadValue(yy) message, /info, 'Camera'+strcompress(cam)+ $ ' dark current'+strcompress(yy_mean)+' ('+strcompress(yy_stdev,/rem)+')' CASE cam OF 1: BEGIN yrange = [0,4] ytickv = [1,2,3] END 2: BEGIN yrange = [0,25] ytickv = [5,10,15] END 3: BEGIN yrange = [0,70] ytickv = [20,40,60] END ENDCASE yticks = n_elements(ytickv) ;offset = floor(min(yy,/nan)/1.0)*1 CASE base_ok[0] EQ -1 OF 0: offset = floor(min(yy[base_ok],/nan)/1.0)*1 1: offset = floor(min(yy,/nan)/1.0)*1 ENDCASE ytitle = 'Dark Current' IF offset NE 0 THEN ytitle = ytitle+'-'+strcompress(offset,/rem) TimeXAxis, /noxtitle, ymargin=[0,0], chars=chars, xmargin=xmargin IF shade_badq THEN PlotCurve, time, badq, /bar, shade=grey, /oplot, /newyaxis, ystyle=4, /noline FOR i=0,norb-1 DO PlotCurve, torb[[i,i]], [0,1], /oplot, /newyaxis, ystyle=4, linestyle=1, /silent PlotCurve, time, yy-offset, base_ok, psym=psym, /oplot, /newyaxis, $ chars=chars, ytitle=ytitle, ystyle=1, yrange=yrange, $ ytickv=ytickv, yticks=yticks, /noclip, /silent, $ /changecolor, color=[drkcolor,saacolor] ;================ ; Squares left and right yy = smei_property(hdr,/squares) IF base_notok[0] NE -1 THEN yy[base_notok] = BadValue(yy) yy_mean = mean(yy, /nan) IF total(finite(yy)) GT 1 THEN yy_stdev = stddev(yy, /nan) ELSE yy_stdev = BadValue(yy) message, /info, 'Camera'+strcompress(cam)+ $ ' squares'+strcompress(yy_mean)+' ('+strcompress(yy_stdev,/rem)+')' yrange = [0,8] ytickv = [2,4,6] yticks = n_elements(ytickv) offset = floor(min(yy,/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 IF shade_badq THEN PlotCurve, time, badq, /bar, shade=grey, /oplot, /newyaxis, ystyle=4, /noline FOR i=0,norb-1 DO PlotCurve, torb[[i,i]], [0,1], /oplot, /newyaxis, ystyle=4, linestyle=1, /silent PlotCurve, time, yy-offset, psym=psym, /oplot, /newyaxis, $ chars=chars, ytitle=ytitle, ystyle=1, yrange=yrange, $ ytickv=ytickv, yticks=yticks, color=sqrcolor, /silent ;================ ; Single center group yy = smei_property(hdr,/center) IF base_notok[0] NE -1 THEN yy[base_notok] = BadValue(yy) yy_mean = mean(yy, /nan) IF total(finite(yy)) GT 1 THEN yy_stdev = stddev(yy, /nan) ELSE yy_stdev = BadValue(yy) message, /info, 'Camera'+strcompress(cam)+ $ ' center'+strcompress(yy_mean)+' ('+strcompress(yy_stdev,/rem)+')' CASE cam 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(yy,/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 ;IF shade_badq THEN PlotCurve, time, badq, /bar, shade=grey, /oplot, /newyaxis, ystyle=4, /noline ;FOR i=0,norb-1 DO PlotCurve, torb[[i,i]], [0,1], /oplot, /newyaxis, ystyle=4, linestyle=1, /silent ;PlotCurve, time, yy-offset, psym=psym, /oplot, /newyaxis, $ ; chars=chars, ytitle=ytitle, ystyle=1, yrange=yrange, $ ; ytickv=ytickv, yticks=yticks, color=pixcolor, /silent ; Pedestal and dark current count message, /info, 'Camera'+strcompress(cam)+' pedestal count' scale = 100.0 yy = smei_property(hdr,/n_pedestal)*4^mode/scale yrange = [0,2024]/scale ytickv = [500,1000,1500]/scale yticks = n_elements(ytickv) TimeXAxis, /noxtitle, ymargin=[0,0], chars=chars, xmargin=xmargin IF shade_badq THEN PlotCurve, time, badq, /bar, shade=grey, /oplot, /newyaxis, ystyle=4, /noline FOR i=0,norb-1 DO PlotCurve, torb[[i,i]], [0,1], /oplot, /newyaxis, ystyle=4, linestyle=1, /silent ytitle = 'Pedestal count/100' PlotCurve, time, yy, psym=psym, /oplot, /newyaxis, $ chars=chars, ytitle=ytitle, ystyle=1, yrange=yrange, $ ytickv=ytickv, yticks=yticks, color=pixcolor, /silent yy = smei_property(hdr,/n_dark_current)*4^mode/scale yrange = [2024,0]/scale ytickv = [500,1000,1500]/scale yticks = n_elements(ytickv) ytitle = 'Dark current count/100' PlotCurve, time, yy, psym=psym, /oplot, /newyaxis, yaxis=0, $ chars=chars, ytitle=ytitle, ystyle=1, yrange=yrange, $ ytickv=ytickv, yticks=yticks, color=sqrcolor, /silent ;================ ; Bodies and camera pointing TimeXAxis, /noxtitle, ymargin=[2,0], chars=chars, xmargin=xmargin IF shade_badq THEN PlotCurve, time, badq, /bar, shade=grey, /oplot, /newyaxis, ystyle=4, /noline FOR i=0,norb-1 DO PlotCurve, torb[[i,i]], [0,1], /oplot, /newyaxis, ystyle=4, linestyle=1, /silent PlotCurve, TimeLimits(time,/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,*]) tmp = where( inside ) IF tmp[0] NE -1 THEN BEGIN 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,count]-1)[ie eq -1] tmp = TimeScale(time[[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(time[[ib,ie]],/mid) phase = jpl_phase(tcntr,/degrees) tcntr = 0.5*(tmp[0]+tmp[1]) dtmp = tmp[1]-tmp[0] 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] = 0 tmp = where( inside ) ENDWHILE ENDFOR PlotCurve, time, pos_camera[1,*], 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, time, AngleRange(pos_camera[0,*],/pi,/deg), $ psym=psym, /oplot, chars=chars, color=lngcolor, /silent PlotCurve, time, pos_camera[2,*], 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(cam)+' '+strcompress(count)+' frames on '+dbname ; Print time and version number 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))+ $ ' (V'+string(version,format='(F4.2)')+')' IF IsType(destination, /defined) THEN BEGIN tmp = ([destination, getenv('TUB')])[IsType(remote,/defined)] CASE one_day OF 0: img_file = filepath(root=tmp, 'c'+strcompress(cam,/rem)+'png_'+ $ strjoin(TimeGet(trange , /_ydoy, upto=upto),'_')+'.png') 1: img_file = filepath(root=tmp, 'c'+strcompress(cam,/rem)+'png_'+ $ strjoin(TimeGet(trange[0], /_ydoy, upto=uday),'_')+'.png') ENDCASE ENDIF get_page, img_file, printer=printer, zbuffer=zbuffer, /new IF IsType(remote,/defined) THEN BEGIN tmp = 'scp '+img_file+' '+remote+':'+destination print, tmp spawn, tmp tmp = do_file(img_file, /delete) ENDIF ENDFOR !p.multi = 0 RETURN & END