FUNCTION smei_orbits_bad, val, old_val, cval @compile_opt.pro ; On error, return to caller CASE val EQ old_val OF 0: BEGIN CASE 0 LE val AND val LE n_elements(cval)-1 OF 0: cstr = ' bad'+string(replicate(32B,strlen(cval[0])-4 > 0)) 1: cstr = cval[val] ENDCASE END 1: cstr = string(replicate(32B,strlen(cval[0]))) ENDCASE RETURN, cstr & END ;+ ; NAME: ; smei_orbits_stat ; PURPOSE: ; Extracts information about frame counts and state changes from ; the SMEI data base. The information is stored in ASCII files. ; CATEGORY: ; camera/idl/toolbox ; CALLING SEQUENCE: PRO smei_orbits_stat, trange , $ destination = destination , $ update = update , $ state_changes = state_changes , $ camera = camera , $ mode = mode , $ ndoy_lag = ndoy_lag , $ silent = silent , $ source = source , $ tnow = tnow , $ usedb = usedb , $ instant_write = instant_write , $ force = force ; INPUTS: ; trange ; OPTIONAL INPUT PARAMETERS: ; /state_changes if NOT set then frame counts are made only. ; if SET then a log of state changes over time is made ; ; /update /update is ignored if trange is set. ; if set then the existing ASCII files are updated ; ; source=source scalar; type: string; default: SMEIDB? ; specifies the location of the SMEI data base ; (passed to href=smei_getfile=). ; destination=destination ; scalar; type: string ; destination directory for the ASCII data base ; files. ; /update NOT: default: $TUB ; /update SET: default: $SSWDB_SMEI/cat/list ; ; camera=camera scalar or array[2]; type: integer; default: [1,3] ; ignored if /state_changes is NOT set ; create/update state changes for specified cameras only ; ; mode=mode scalar; type: integer ; ignored if /state_changes is SET ; if set the frame counts are for the specified mode ; only (by default all three modes are combined) ; ; tnow=tnow array[1]; type: time structure; default: TimeSystem() ; ignored when /state_changes is set ; sets the end time when /update is set ; ; ndoy_lag scalar; type: integer; default: -3 ; sets overlap with existing ASCII files when /update ; is set (i.e. the last ndoy_lag days in the ASCII ; files is redone). ; ; /usedb by default the header data base is used. ; If /usedb is set the frame data base is used ; (this takes a lot longer) ; silent=silent scalar; type: integer; default: 0 ; controls level of informational messages ; OUTPUTS: ; (to ASCII files; see PROCEDURE) ; INCLUDE: @compile_opt.pro ; On error, return to caller ; CALLS: ; InitVar, IsType, smeidb_mounted, CheckDir, txt_read, flt_string ; TimeUnit, TimeSet, TimeOp, TimeGet, TimeSystem ; smei_coriolis, smei_hdr_get, smei_getfile, boost ; do_file, destroyvar, smei_property, smei_orbit_get ; PROCEDURE: ; /state_changes NOT set (i.e. frame counts only) ; if no mode is specified then create/update files ; destination/smei_frm_day.txt and destination/smei_frm_orb.txt ; if mode is specified then create/update files ; destination/smei_frm_day_m#.txt and destination/smei_frm_orb_m#.txt ; (where # is 0,1,2) ; ; /state_changes SET (i.e. state changes only) ; create/update files destination/smei_state_cam#.txt' ; where # is 1,2,3 ; MODIFICATION HISTORY: ; SEP-2005, Paul Hick (UCSD/CASS) ; MAR-2007, Paul Hick (UCSD/CASS) ; Added counters for frames that satisfy the default test ; criteria used by smeidb_sky to select frames for skymap ; construction. ; APR-2008, Paul Hick (UCSD/CASS; pphick@ucsd.edu) ; Added timestamp to header ;- InitVar, silent , 0 InitVar, daily , /key InitVar, state_changes, /key InitVar, update , /key InitVar, usedb , /key InitVar, instant_write, /key InitVar, force , /key update AND= IsType(trange, /undefined) CASE update of 0: InitVar, destination, getenv('TUB') 1: InitVar, destination, filepath( root=getenv('SSWDB_SMEI'), subdir='cat', 'list') ENDCASE IF usedb THEN IF NOT smeidb_mounted() THEN RETURN IF NOT CheckDir(destination) THEN RETURN uday = TimeUnit(/day) usec = TimeUnit(/sec) CASE state_changes OF 0: BEGIN CASE IsType(mode,/defined) OF 0: BEGIN file_day = filepath(root=destination,'smei_frm_day.txt') file_orb = filepath(root=destination,'smei_frm_orb.txt') END 1: BEGIN tmp = strcompress(mode,/rem) file_day = filepath(root=destination,'smei_frm_day_m'+tmp+'.txt') file_orb = filepath(root=destination,'smei_frm_orb_m'+tmp+'.txt') END ENDCASE IF force OR txt_read(file_day, data_day) NE 1 THEN BEGIN tmp = TimeGet(TimeSystem(/silent),format='YYYY/MN/DD (DOY) hh:mm') data_day = [ $ 'Number of frames per day for each camera @ '+tmp , $ 'Totals give the sum of the indicated columns' , $ 'Col 1 : Date' , $ 'Col 2, 3, 4, 5: Nr frames per day (cam 1,2,3, 1+2+3)' , $ 'Col 6, 7, 8, 9: Nr good frames per day (cam 1,2,3 1+2+3)' , $ '"good" frames are accepted by smei_skyd in default mode' , $ '' , $ 'YYYY_DOY Cam 1 Cam 2 Cam 3 Cam 1 Cam 2 Cam 3 ' , $ '========================================================================================' , $ 'TOTAL 0 0 0 0 0 0 0 0' , $ '========================================================================================' , $ '2002_365 0 0 0 0 0 0 0 0'] data_orb = [ $ 'Number of frames per orbit for each camera @ '+tmp , $ 'Totals give the sum of the indicated columns' , $ 'Col 1 : Orbit number' , $ 'Col 2, 3, 4 : Orbit start time (date, doy, time of day)' , $ 'Col 5, 6, 7, 8: Nr frames per orbit (cam 1,2,3, 1+2+3)' , $ 'Col 9,10,11,12: Nr good frames per orbit (cam 1,2,3 1+2+3)', $ '"good" frames are accepted by smei_skyd in default mode' , $ '' , $ ' Cam 1 Cam 2 Cam 3 Cam 1 Cam 2 Cam 3 ', $ '======================================================================================================================', $ ' TOTAL 0 0 0 0 0 0 0 0', $ '======================================================================================================================', $ ' 0 2002/12/31 (365) 22:15:05.410 0 0 0 0 0 0 0 0' ] IF IsType(mode,/defined) THEN BEGIN data_orb[0] += ' for mode'+strcompress(mode) data_day[0] += ' for mode'+strcompress(mode) ENDIF ndoy_lag = 0 ENDIF ELSE BEGIN IF txt_read(file_orb, data_orb) NE 1 THEN RETURN InitVar, ndoy_lag, -14 ENDELSE format = 'YEAR/MN/DD (DOY) hh:mm:ss.mss' plen_day = 8 ; Start position of frame counters ptot_day = (where(strpos(data_day,'TOTAL') NE -1))[0] ; Record with frame totals pdoy_day = (where(strpos(data_day,'=====') EQ 0))[1]+1 ; First record with data for days plen_orb = 38 ; Start position of frame counters ptot_orb = (where(strpos(data_orb,'TOTAL') NE -1))[0] ; Record number with frame totals pdoy_orb = (where(strpos(data_orb,'=====') EQ 0))[1]+1 ; First record with data for orbits FOR i=0L,pdoy_day DO print, data_day[i] print print FOR i=0L,pdoy_orb DO print, data_orb[i] tmp = flt_string( strmid( data_day[ptot_day], plen_day), fmt=fmt_tot_day ) ; 8I10 tmp = flt_string( strmid( data_day[pdoy_day], plen_day), fmt=fmt_cnt_day ) ; 8I10 tday = TimeSet( strmid( data_day[pdoy_day], 0, plen_day) ) ; Most recent day processed tmp = flt_string( strmid( data_orb[ptot_orb], plen_orb), fmt=fmt_tot_orb ) ; 8I10 tmp = flt_string( strmid( data_orb[pdoy_orb], plen_orb), fmt=fmt_cnt_orb ) ; 8I10 tmp = flt_string( strmid( data_orb[pdoy_orb], 0, plen_orb-strlen(format)), fmt=fmt_orb, lenfmt=lenfmt) ; I6 pad = strjoin(replicate(' ',plen_orb-strlen(format)-lenfmt)) last_orbit = round(tmp[0]) pdoy_lag = pdoy_day-ndoy_lag tlag = TimeOp(/add, tday, TimeSet(/diff, day=ndoy_lag)) InitVar, tnow, TimeGet( TimeSystem(/silent), uday, /eot) ndoy = TimeOp(/subtract, tnow, tlag, uday) orbit = TimeGet(/smei,tlag) orbit = smei_orbit_get(orbit,/ceil) porb_lag = pdoy_orb+last_orbit-orbit nc = lonarr(3) ncc_all = lonarr(3) ncc_good = lonarr(3) ptr_time = ptrarr(3, /allocate) ptr_just_bad = ptrarr(3, /allocate) ptr_bad_quat = ptrarr(3, /allocate) ptr_shutter = ptrarr(3, /allocate) ptr_base_ok = ptrarr(3, /allocate) FOR i=0L,ndoy-1 DO BEGIN tday = TimeOp(/add, tlag, TimeSet(/diff, day=i+[0,1])) FOR cam=0,2 DO BEGIN CASE usedb OF 0: BEGIN ; Use hdr files smei_hdr_get, tday , $ camera = cam+1 , $ mode = mode , $ count = count , $ silent = silent , $ time = time , $ get = ['just_bad','bad_quat','shutter','base_ok'],$ one = just_bad , $ two = bad_quat , $ three = shutter , $ four = base_ok END 1: BEGIN ; Use SMEI frames directly hdr = smei_getfile( tday, $ camera = cam+1 , $ mode = mode , $ count = count , $ silent = silent , $ source = source , $ /get_hdr) IF count GT 0 THEN BEGIN time = smei_property(hdr, /time) just_bad = smei_property(hdr, /just_bad) bad_quat = smei_property(hdr, /bad_quaternion) shutter = smei_property(hdr, /shutter_open) base_ok = smei_property(hdr, /base_ok) ENDIF END ENDCASE ncc_all [cam] = count ncc_good[cam] = count IF count EQ 0 THEN $ CONTINUE ; Add frames in current day CASE nc[cam] NE 0 OF 0: BEGIN *ptr_time [cam] = time *ptr_just_bad[cam] = just_bad *ptr_bad_quat[cam] = bad_quat *ptr_shutter [cam] = shutter *ptr_base_ok [cam] = base_ok END 1: BEGIN *ptr_time [cam] = [*ptr_time [cam], time ] *ptr_just_bad[cam] = [*ptr_just_bad[cam], just_bad] *ptr_bad_quat[cam] = [*ptr_bad_quat[cam], bad_quat] *ptr_shutter [cam] = [*ptr_shutter [cam], shutter ] *ptr_base_ok [cam] = [*ptr_base_ok [cam], base_ok ] END ENDCASE nc[cam] += count tmp = where(1-just_bad AND 1-bad_quat AND shutter AND base_ok, nn) ncc_good[cam] = nn ; Frames OK for smeidb_sky ENDFOR tmp = [ncc_all,round(total(ncc_all)),ncc_good,round(total(ncc_good))] boost, xdata_day, $ TimeGet(format='YEAR_DOY', $ TimeOp(/add, tlag, TimeSet(/diff, day=i)))+ $ ; Day of year as YYYY_DOY string(tmp,format=fmt_cnt_day) ; While end of orbit in current day WHILE TimeOp(/subtract, smei_coriolis(orbit+1), tday[1], usec) LT 0 DO BEGIN torb = smei_coriolis( orbit+[0,1] ) dorb = TimeOp(/subtract, torb[1], torb[0], usec) ; Orbital period FOR cam=0,2 DO BEGIN CASE nc[cam] EQ 0 OF 0: BEGIN ; Time from start of orbit dtime = TimeOp(/subtract, *ptr_time[cam], torb[0], usec) ; Find number of frames OK for smeidb_sky for this orbit tmp = where( 0 LE dtime AND dtime LT dorb AND $ ; Inside orbit 1-*ptr_just_bad[cam] AND $ ; Not "just bad" 1-*ptr_bad_quat[cam] AND $ ; Not a bad quaternion *ptr_shutter [cam] AND $ ; Shutter open *ptr_base_ok [cam], nn ) ; Ped and dark current OK ncc_good[cam] = nn ; Find number of frames for this orbit tmp = where( 0 LE dtime AND dtime LT dorb, nn, complement=rest, ncomplement=n ) ncc_all[cam] = nn ; Number of frames in this orbit nc [cam] = n ; Remaining number of frames (in later orbits) IF nn*n NE 0 THEN BEGIN ; Retain remaining frames in later orbits *ptr_time [cam] = (*ptr_time [cam])[rest] *ptr_just_bad[cam] = (*ptr_just_bad[cam])[rest] *ptr_bad_quat[cam] = (*ptr_bad_quat[cam])[rest] *ptr_shutter [cam] = (*ptr_shutter [cam])[rest] *ptr_base_ok [cam] = (*ptr_base_ok [cam])[rest] ENDIF END 1: BEGIN ncc_all [cam] = 0 ; No frames in this orbit ncc_good[cam] = 0 END ENDCASE ENDFOR tmp = [ncc_all,round(total(ncc_all)),ncc_good,round(total(ncc_good))] boost, xdata_orb, $ string(orbit, format=fmt_orb) + $ ; Orbit number pad + $ ; White space TimeGet(format=format, torb[0]) + $ ; Orbit start time string(tmp,format=fmt_cnt_orb) orbit += 1 ; Increase orbit counter ENDWHILE ENDFOR xdata_day = reverse(xdata_day) xdata_orb = reverse(xdata_orb) xdata_day = [ data_day[0:pdoy_day-1], xdata_day ] IF pdoy_lag+1 LT n_elements(data_day) THEN xdata_day = [ xdata_day, data_day[pdoy_lag+1:*] ] xdata_orb = [ data_orb[0:pdoy_orb-1], xdata_orb ] IF porb_lag+1 LT n_elements(data_orb) THEN xdata_orb = [ xdata_orb, data_orb[porb_lag+1:*] ] tmp = round(flt_string(fmt_cnt_day)) ; [8,10] extracted from 8I10 n = n_elements(xdata_day[pdoy_day:*]) cnt = lonarr( tmp[0], n ) cnt = reform( cnt, tmp[0], n, /overwrite ) ; Needed for n=1 reads, strmid(xdata_day[pdoy_day:*],plen_day), format=fmt_cnt_day, cnt ; Sum all 8 columns cnt = round( total(cnt,2) ) xdata_day[ptot_day] = strmid(xdata_day[ptot_day],0,plen_day)+string(cnt, format=fmt_tot_day) tmp = round(flt_string(fmt_cnt_orb)) ; [8,10] extracted from 8I10 n = n_elements(xdata_orb[pdoy_orb:*]) cnt = lonarr( tmp[0], n ) cnt = reform( cnt, tmp[0], n, /overwrite ) ; Needed for n=1 reads, strmid(xdata_orb[pdoy_orb:*],plen_orb), format=fmt_cnt_orb, cnt ; Sum all 8 columns cnt = round( total(cnt,2) ) xdata_orb[ptot_orb] = strmid(xdata_orb[ptot_orb],0,plen_orb)+string(cnt, format=fmt_tot_orb) FOR cam=0,2 DO BEGIN IF ptr_valid(ptr_time [cam]) THEN ptr_free, ptr_time [cam] IF ptr_valid(ptr_just_bad[cam]) THEN ptr_free, ptr_just_bad[cam] IF ptr_valid(ptr_bad_quat[cam]) THEN ptr_free, ptr_bad_quat[cam] IF ptr_valid(ptr_shutter [cam]) THEN ptr_free, ptr_shutter [cam] IF ptr_valid(ptr_base_ok [cam]) THEN ptr_free, ptr_base_ok [cam] ENDFOR openw, /get_lun, iu, file_day+'x' FOR i=0L, n_elements(xdata_day)-1 DO printf, iu, xdata_day[i] free_lun, iu openw, /get_lun, iu, file_orb+'x' FOR i=0L, n_elements(xdata_orb)-1 DO printf, iu, xdata_orb[i] free_lun, iu sts = do_file(/move, file_day+'x', file_day) sts = do_file(/move, file_orb+'x', file_orb) END 1: BEGIN InitVar, ndoy_lag, -14 space = byte(' ') equal = byte('=') equals = string( replicate(equal, 95) ) cmode = ' '+['1x1 ' ,'2x2 ','4x4 '] cshutter = ' '+['close ','open ' ] cled = ' '+['off' ,'on ' ] cflatf = ' '+['off' ,'on ' ] croi = ' '+['????' ,'full','????','EMC ','UCSD'] cquat = ' '+['good' ,'bad ' ] cbos = ' '+['off ' ,'on ' ] torbit = TimeGet(smei_coriolis(/orbital_period), uday, /full, /diff) InitVar, camera, [1,3] InitVar, camera, [camera,camera], count=1 FOR cam=camera[0],camera[1] DO BEGIN file = filepath(root=destination,'smei_state_cam'+strcompress(cam,/rem)+'.txt') IF update THEN BEGIN ; Don't replace by case block ('continue' not allowed inside case) IF txt_read(file, data) NE 1 THEN BEGIN ; Initialize new file if it doesn't exist yet. CASE cam OF 1: data = '2003/01/11 (011) 1x1 close off off UCSD off 0 29.21' 2: data = '2003/01/13 (013) 1x1 close off off UCSD off 0 28.50' 3: data = '2003/01/13 (013) 1x1 close off off UCSD off 0 29.21' ENDCASE data = [ $ '===============================================================================================', $ ' mode shutter LED FF ROI QUAT BOSA BOSC t+.1 T+5' , $ data , $ '==============================================================================================='] ENDIF n = where(data EQ equals) ; For ndoy_lag=1 this picks up the start of the last day on file ; (between the two rows of equal signs). ; For smaller values of ndoy_lag step back the appropriate number ; of days. uu = (n_elements(n)-1+2*(ndoy_lag-1)) > (-1) IF uu NE -1 THEN uu = n[uu]-4 tt = TimeSet( (strtok(data[uu+3],/extract))[0] ) tt = TimeOp(/add, tt, TimeSet(/diff,[0,1],uday)) ; Keep data upto time tt. The start of day tt (the group of lines bracketed ; by equal signs) is dropped here, and will be recalculated below. IF uu EQ -1 THEN destroyvar, data ELSE data = data[0:uu] ; Search back from time tt until a frame is found. Usually this picks up the ; last frame of the preceding day (unless there are data gaps). uu = tt REPEAT BEGIN uu = TimeOp(/subtract, uu, TimeSet(/diff,1,uday)) CASE usedb OF 0: smei_hdr_get, uu, count=count, camera=cam, silent=silent, time=hdr 1: hdr = smei_getfile(uu, count=count, camera=cam, silent=silent, source=source) ENDCASE ENDREP UNTIL count NE 0 ; Get the header for the last frame. This is used to initialize the old_* values. CASE usedb OF 0: smei_hdr_get, hdr[[count-1,count-1]], camera=cam, silent=silent, hdr=hdr 1: hdr = smei_getfile(hdr[count-1], /exist, /get_hdr, silent=silent, source=source) ENDCASE old_tframe = smei_property(hdr, /time ) old_mode = smei_property(hdr, /mode ) old_shutter = smei_property(hdr, /shutter ) old_led = smei_property(hdr, /led_enabled ) old_flatf = smei_property(hdr, /onboard_ff_enabled) old_roi = smei_property(hdr, /roi_map ) old_bad_quat= smei_property(hdr, /bad_quaternion) old_bos_on = smei_property(hdr, /bos_alert ) old_bos_ch = smei_property(hdr, /bos_change ) old_temp = smei_property(hdr, /ccd_temp ) > (-99.99) tmaybe = TimeSystem(/silent) InitVar, ndoy_len, 100 IF TimeOp(/subtract,tmaybe,tt[0],uday) GT ndoy_len THEN $ tmaybe = TimeOp(/add,tt[0],TimeSet(/diff,day=ndoy_len)) trange = [ tt[0], TimeGet(tmaybe,/eot,uday) ] message,/info, 'processing '+strjoin(TimeGet(/ydoy,trange,upto=uday),'-') init_old_values = 0 ENDIF ELSE BEGIN destroyvar, data init_old_values = 1 ENDELSE ndays = TimeGet(trange, uday, /full) IF instant_write THEN BEGIN openw, /get_lun, iu, file+'x' FOR i=0L,n_elements(data)-1 DO printf, iu, data[i] ENDIF first_frame_of_day = 1 FOR day=ndays[0],ndays[1] DO BEGIN tt = TimeSet(day+[0,1],uday) CASE usedb OF 0: smei_hdr_get, tt, hdr=hdr, count=count, camera=cam, silent=silent 1: hdr = smei_getfile(tt, count=count, /get_hdr, camera=cam, silent=silent, source=source) ENDCASE IF count EQ 0 THEN CONTINUE ; No frames found: go to next day tframe = smei_property(hdr, /time ) mode = smei_property(hdr, /mode ) shutter = smei_property(hdr, /shutter ) led = smei_property(hdr, /led_enabled ) flatf = smei_property(hdr, /onboard_ff_enabled) roi = smei_property(hdr, /roi_map ) bad_quat= smei_property(hdr, /bad_quaternion) bos_on = smei_property(hdr, /bos_alert ) bos_ch = smei_property(hdr, /bos_change ) temp = smei_property(hdr, /ccd_temp ) > (-99.99) IF first_frame_of_day THEN BEGIN cstr = TimeGet(format='YEAR/MN/DD (DOY)',tt[0])+string(replicate(space,13+2))+ $ smei_orbits_bad(mode [0], -1, cmode ) + $ smei_orbits_bad(shutter [0], -1, cshutter) + $ smei_orbits_bad(led [0], -1, cled ) + $ smei_orbits_bad(flatf [0], -1, cflatf ) + $ smei_orbits_bad(roi [0], -1, croi ) + $ smei_orbits_bad(bad_quat[0], -1, cquat ) + $ smei_orbits_bad(bos_on [0], -1, cbos ) + $ strcompress(bos_ch[0])+string(replicate(space,3+5)) + $ string(temp[0], format='(F6.2)') cstr = $ [ equals, $ string(replicate(space,31))+' mode shutter LED FF ROI QUAT BOSA BOSC t+.1 T+5', $ strtrim(cstr), $ equals ] CASE instant_write OF 0: boost, data, cstr 1: FOR i=0L,n_elements(cstr)-1 DO printf, iu, cstr[i] ENDCASE first_frame_of_day = 0 IF init_old_values THEN BEGIN old_tframe = tframe old_mode = mode old_shutter = shutter old_temp = temp old_roi = roi old_led = led old_flatf = flatf old_bad_quat= bad_quat old_bos_on = bos_on old_bos_ch = bos_ch init_old_values = 0 ENDIF ENDIF FOR i=0L,count-1 DO BEGIN cstr = smei_orbits_bad(mode [i], old_mode , cmode ) + $ smei_orbits_bad(shutter [i], old_shutter , cshutter) + $ smei_orbits_bad(led [i], old_led , cled ) + $ smei_orbits_bad(flatf [i], old_flatf , cflatf ) + $ smei_orbits_bad(roi [i], old_roi , croi ) + $ smei_orbits_bad(bad_quat[i], old_bad_quat, cquat ) + $ smei_orbits_bad(bos_on [i], old_bos_on , cbos ) CASE bos_ch [i] OF old_bos_ch : cstr = cstr+string(replicate(space,5)) ELSE : cstr = cstr+strcompress(old_bos_ch)+'->'+strcompress(bos_ch[i],/rem) ENDCASE IF TimeOp(tframe[i],old_tframe,/subtract,uday) GT torbit/10 THEN cstr = cstr+' gap ' ELSE cstr = cstr+' ' IF abs(temp[i]-old_temp) GT 5.0 THEN $ cstr = cstr+string(old_temp, format='(F6.2)')+'->'+string(temp[i], format='(F6.2)') IF strtrim(cstr) NE '' THEN BEGIN cstr = TimeGet(old_tframe, /_ydoy, upto=usec)+' -> '+ $ TimeGet(tframe[i] , /_ydoy, from=uday, upto=usec)+' '+cstr cstr = strtrim(cstr) CASE instant_write OF 0: boost, data, cstr 1: printf, iu, cstr ENDCASE ENDIF old_tframe = tframe [i] old_mode = mode [i] old_shutter = shutter [i] old_temp = temp [i] old_roi = roi [i] old_led = led [i] old_flatf = flatf [i] old_bos_on = bos_on [i] old_bos_ch = bos_ch [i] old_bad_quat= bad_quat[i] ENDFOR first_frame_of_day = 1 ENDFOR IF NOT instant_write THEN BEGIN openw, /get_lun, iu, file+'x' FOR i=0L,n_elements(data)-1 DO printf, iu, data[i] ENDIF free_lun, iu sts = do_file(/move, file+'x', file) ENDFOR END ENDCASE RETURN & END