;+ ; $Id: wcs_combine.pro,v 1.33 2025/05/15 12:49:55 mcnutt Exp $ ; Project : STEREO - SECCHI ; ; Name : SCC_COMBINE ; ; Purpose : combine images onto a full field of view using the WCS. ; ; Explanation : ; ; Use : SCC_COMBINE_MVI ; ; Example: ; Inputs : files ; ; Optional Inputs : ; ; Outputs : imo,file_hdr ; ; Keywords : hdrs= - required if using image arrays as input without file names. ; /truecolor - set to create true color frames ; hsize= - sets output horizontal (X) size; =-1 means fit to screen ; /first - set to indicate first frame of movie , if set the movie file_hdr will be populated ; usemask= - array of outer mask sizes in solar radii, use 0 for no mask ; xminmax= - xrange ; yminmax= - yrange ; /rtheta - creates a rtheta movie set to 2 for log scale ; /fmask - mask fits to be used if usemask is eq -1 ; bkgclr= - background color ; ctable= - color tables for true color movies ; upwcshdrhrs= sets how often to read in wcs headers cadence in hours ; maskindeg = set to indicate units of input usemask is in degrees ; ; Calls : parse_secchi_filename.pro, define_wcshdrs.pro, tvcircle.pro, heliorad2heliocart.pro, ; wcs_get_pixel.pro, sccreadfits.pro, read_png.pro, read_gif.pro, read_jpeg.pro ; ; Category : Image Processing/Display Movie Animation ; ; Prev. Hist. : None. ; ; Written : Lynn Hutting, NRL, May 2011. ; $Log: wcs_combine.pro,v $ ; Revision 1.33 2025/05/15 12:49:55 mcnutt ; checkin commit status ; ; Revision 1.32 2025/04/03 13:39:51 mcnutt ; corrected color issues between true color and tables ; ; Revision 1.31 2018/06/11 14:41:40 mcnutt ; updated call to tvcircle ; ; Revision 1.30 2012/11/16 16:12:59 mcnutt ; corrected grayscale error created when adding ab movie options ; ; Revision 1.29 2012/08/29 14:12:06 mcnutt ; added wcs_combine bpos options ; ; Revision 1.28 2012/08/08 12:08:36 mcnutt ; set default masks to rsun ; ; Revision 1.27 2012/08/07 19:09:23 mcnutt ; added maskindeg keyword to allow input mask in units of deg ; ; Revision 1.26 2012/08/03 13:24:35 mcnutt ; corrected common block ; ; Revision 1.25 2012/07/24 13:16:23 mcnutt ; changes imo to bytes before return ; ; Revision 1.24 2012/07/24 12:57:08 mcnutt ; change interpolate bytes and not convert to float to make compatible with scc_save_mvframe ; ; Revision 1.23 2012/07/23 14:25:34 mcnutt ; check for ext2 to be defined before check for web download ; ; Revision 1.22 2012/07/19 14:59:21 mcnutt ; check sock_get status ; ; Revision 1.21 2012/07/16 21:59:33 nathan ; fill in procedure calls ; ; Revision 1.20 2012/07/16 14:59:35 mcnutt ; corrected first order if using fits files ; ; Revision 1.19 2012/07/13 12:23:03 mcnutt ; uses sock_get to download web images ; ; Revision 1.18 2012/03/27 17:34:00 mcnutt ; made compatiable with TVCICLE ; ; Revision 1.17 2011/11/09 19:02:58 mcnutt ; checking for updates ; ; Revision 1.16 2011/09/30 18:37:36 mcnutt ; added upwcshdrhrs keyword to set hrs to update wcs headers ; ; Revision 1.15 2011/09/29 18:53:39 mcnutt ; will update wscc_pngplay widget coords if open ; ; Revision 1.14 2011/09/28 18:50:04 nathan ; change VSIZE= to HSIZE=; do fit-to-screen if hsize<0 ; ; Revision 1.13 2011/09/26 18:30:14 mcnutt ; added latplane movie grrid and measuring options ; ; Revision 1.12 2011/09/21 21:20:24 nathan ; Always recompute wcs for HI1-B ; ; Revision 1.11 2011/09/20 16:11:31 mcnutt ; will not mask largest image if usemask keyword not set ; ; Revision 1.10 2011/08/26 15:09:43 mcnutt ; changed jpgs ctable to clrtable not get confused keyword ctable ; ; Revision 1.9 2011/08/26 14:58:29 mcnutt ; added keywords for wcs_combine_mvi ; ; Revision 1.8 2011/08/09 18:50:50 mcnutt ; added (xy)minmax keyword to set (xy)ranges ; ; Revision 1.7 2011/08/05 18:39:29 mcnutt ; added user defined masks to rtheta movies ; ; Revision 1.6 2011/08/05 13:58:28 mcnutt ; corrected ymax and xmax for rtheta movies ; ; Revision 1.5 2011/08/04 16:42:34 mcnutt ; added cname to call to parse_secchi_filename to work with wavelet files ; ; Revision 1.4 2011/08/03 18:00:21 mcnutt ; added program header ; function wcs_combine,files,file_hdr,frame_hdr,hdrs=hdrs,truecolor=truecolor, hsize=hsize,first=first,usemask=usemask,frametime= frametime, $ rtheta=rtheta,xminmax=xminmax,yminmax=yminmax,ctable=ctable,bkgclr=bkgclr, fmask=fmask,upwcshdrhrs=upwcshdrhrs, maskindeg=maskindeg, $ abmovie=abmovie, _EXTRA=_extra common wcs_comb,coord,masks,imo,rimo,gimo,bimo,imsizeout,cdate,wcssecchi,wcshdr,wcssoho,wcsptr,cfile_hdr,cdelts,wcsorder,coord2,imo2,rimo2,gimo2,bimo2,dets COMMON scc_png_COMMON,pngvar,imglist,cadencemins,times, wevent if keyword_set(first) then begin undefine,imsizeout undefine,wcshdrs undefine,file_hdr undefine,dets cdate='1958/01/01 00:00:00' endif help,first,files,file_hdr if keyword_set(rtheta) then rtheta=rtheta else rtheta=0 if rtheta eq 2 then islog=1 else islog=0 if keyword_set(truecolor) then truecolor=1 else truecolor=0 IF keyword_set(HSIZE) THEN hsize=hsize ELSE hsize=512 len=n_elements(files) if datatype(files) eq 'PTR' and ~keyword_set(hdrs) then begin print,'Headers must be supplied; input is not a file name' return,-1 endif detectors=['HI2A','HI1A','COR2A','COR1A','EUVIA','EUVIB','COR1B','COR2B','HI1B','HI2B','C3','C2','EIT','AIA','HDMI','MDI'] outer=[0,0,15.,3.5,1.5,1.5,3.5,15.,0,0,0,4.25,1.25,1.35,1.35,1.35] scv=['A','A','A','A','A','B','B','B','B','B','E','E','E','E','E','E'] ahdr = {filename:'', $ detector:'', $ date_obs:'', $ time_obs:'', $ r1col:0, r2col:0, r1row:0, r2row:0, $ filter:'', $ polar:'', $ wavelnth:'', $ exptime:0.0, $ ; seconds xcen:0.0, ycen:0.0, $ ; pixels (FITS coordinates) cdelt1:0.0, $ ; arcsec/pixel nx:0.0, $ ; arcsec ny:0.0, $ ; arcsec rsun:0.0, $ ; arcsec roll:0.0 } ; degrees frame_hdr = {filename:'', $ detector:'', $ date_obs:'', $ time_obs:'', $ r1col:0, r2col:0, r1row:0, r2row:0, $ filter:'', $ polar:'', $ wavelnth:'', $ exptime:0.0, $ ; seconds xcen:0.0, ycen:0.0, $ ; pixels (FITS coordinates) cdelt1:0.0, $ ; arcsec/pixel rsun:0.0, $ ; arcsec roll:0.0 } ; degrees if datatype(imsizeout) eq 'UND' then io=0 else io=wcsorder(0) if datatype(files) eq 'STR' then begin BREAK_FILE, files(io), a, dir, name, ext2, /last parse_secchi_filename, name, dobs, det, sc, wvl filenames=files endif else begin ahdr=(*hdrs[io]) dobs=ahdr.date_obs+' '+ahdr.time_obs det=ahdr.detector filenames=ahdr.filename endelse yminmaxs=fltarr(2,n_Elements(files)) xminmaxs=fltarr(2,n_Elements(files)) ; Always recompute wcs for HI1-B ww=where(strpos(filenames,'h1B') GT 0,nh1b) if keyword_set(upwcshdrhrs) then updatcad=upwcshdrhrs else updatcad=2. if (anytim2tai(dobs)-anytim2tai(cdate))/3600. gt updatcad or nh1b GT 0 and anytim2tai(dobs) ne anytim2tai(cdate) then begin sohocnt=0 hdrcnt=0 secchicnt=0 for i=0,len-1 do begin if datatype(files) eq 'STR' then begin BREAK_FILE, files(i), a, dir, name, ext2, /last if ext2 EQ '.fts' then img=sccreadfits(files(i),ahdr,/nodata) else begin if strpos(files(i),'http') eq 0 then begin uname=getenv('HOME')+'/tmp'+ext2 REPEAT BEGIN sock_get,files(i),uname, STATUS=dlstat print,files(i),uname IF dlstat EQ 0 THEN wait,5 print,dlstat ENDREP UNTIL dlstat GE 1 endif else uname=files(i) if ext2 EQ '.png' then ok = QUERY_PNG(uname,s) if ext2 EQ '.gif' then ok = QUERY_GIF(uname,s) if ext2 EQ '.jpg' then ok = QUERY_JPEG(uname,s) parse_secchi_filename, name, dobs, det, sc, wvl, cname ahdr.filename=cname+ext2 ahdr.detector=det ahdr.wavelnth = wvl ahdr.date_obs=strmid(dobs,0,10) ahdr.time_obs=strmid(dobs,11,8) ahdr.nx=s.DIMENSIONS(0) ahdr.ny=s.DIMENSIONS(1) ahdr.roll = 0. endelse endif else begin ahdr=(*hdrs[i]) sc=strmid(ahdr.FILENAME ,strpos(ahdr.FILENAME[0],'.')-1,1) det=ahdr.detector endelse if rtheta gt 0 then system='B' define_wcshdrs,hdrs=ahdr,wcs=wcs,system=system if datatype(imsizeout) eq 'UND' then begin coords=wcs_get_coord(wcs) if wcs.cunit(0) eq 'arcsec' then coords=coords/3600. yminmaxs(*,i)=[min(coords(1,*,*)),max(coords(1,*,*))] xminmaxs(*,i)=[min(coords(0,*,*)),max(coords(0,*,*))] IF sc NE 'A' and sc NE 'B' THEN sc='' if i eq 0 then dets=det+sc else dets=[dets,det+sc] endif print,det if sc eq 'A' or sc eq 'B' then begin if secchicnt eq 0 then wcssecchi=wcs else wcssecchi=[wcssecchi,wcs] if i eq 0 then wcsptr=[ptr_new(wcssecchi(secchicnt))] else wcsptr=[wcsptr,ptr_new(wcssecchi(secchicnt))] secchicnt=secchicnt+1 endif else if wcs.position.soho eq 1 then begin if sohocnt eq 0 then wcssoho=wcs else wcssoho=[wcssoho,wcs] if i eq 0 then wcsptr=[ptr_new(wcssoho(sohocnt))] else wcsptr=[wcsptr,ptr_new(wcssoho(sohocnt))] sohocnt=sohocnt+1 endif else begin if hdrcnt eq 0 then wcshdr=wcs else wcshdr=[wcshdr,wcs] if i eq 0 then wcsptr=[ptr_new(wcshdr(hdrcnt))] else wcsptr=[wcsptr,ptr_new(wcshdr(hdrcnt))] hdrcnt=hdrcnt+1 endelse if i eq 0 then cdelts=wcs.cdelt(0) else cdelts=[cdelts,wcs.cdelt(0)] endfor cdate=dobs sm=where(cdelts lt 0.2,cnt) if cnt gt 0 then cdelts(sm)=cdelts(sm)*3600 wcsorder=reverse(sort(cdelts)) endif if datatype(imsizeout) eq 'UND' then begin if rtheta gt 0 then begin if keyword_set(yminmax) Then begin yminmaxt = yminmax yminmax = xminmax endif if keyword_set(xminmax) Then xminmax = yminmaxt endif if not keyword_set(yminmax) Then begin if rtheta eq 0 then yminmax=[min(yminmaxs(0,*)),max(yminmaxs(1,*))] else yminmax=[0,max(abs(xminmaxs(*,*)))] if islog then yminmax(0)=0.05 endif else yminmax=yminmax if not keyword_set(xminmax) Then begin if rtheta eq 0 then xminmax=[min(xminmaxs(0,*)),max(xminmaxs(1,*))] else xminmax=[0,360] endif else xminmax=xminmax ysiz=(yminmax(1)-yminmax(0)) xsiz=(xminmax(1)-xminmax(0)) arat=float(xsiz)/ysiz IF hsize LT 0 THEN BEGIN ; fit to screen device,get_screen_size=ss wsizes=define_widget_sizes() ssx=ss[0]-2*wsizes.border ssy=ss[1]-(2*wsizes.border+wsizes.onerow+wsizes.dsktop+wsizes.winhdr+20) ydif=ssy-ysiz xdif=ssx-xsiz IF ydif LT xdif THEN $ hsize=arat*ssy ELSE $ hsize=ssx ENDIF if rtheta eq 0 then vsize=fix(hsize/arat) else vsize=360*(hsize/512) imsizeout=[hsize,vsize] ;if rtheta gt 0 then outer=[0,0,4.,1.,.35,.35,1.,4.,0,0,8.,1.7,.4,.4,.4,.4] input mask are now in rsun by default masks=fltarr(len,imsizeout[0],imsizeout[1]) coord=fltarr(2,imsizeout[0],imsizeout[1]) if rtheta eq 0 then begin lat=replicate(1,imsizeout[1])##lgen(imsizeout[0],xminmax) lng=lgen(imsizeout[1],yminmax)##replicate(1,imsizeout[0]) coord[0,*,*]=lat coord[1,*,*]=lng cx=find_closest(0.0,coord[0,*,0]) cy=find_closest(0.0,coord[1,0,*]) if keyword_set(abmovie) then begin coord2=coord if rtheta eq 0 then xminmax2=xminmax(sort(xminmax*(-1)))*(-1) else xminmax2=xminmax lat=replicate(1,imsizeout[1])##lgen(imsizeout[0],xminmax2) lng=lgen(imsizeout[1],yminmax)##replicate(1,imsizeout[0]) coord2[0,*,*]=lat coord2[1,*,*]=lng cx2=find_closest(0.0,coord2[0,*,0]) cy2=find_closest(0.0,coord2[1,0,*]) endif ;set_plot,'z' ;device,set_resolution=[imsizeout(0),imsizeout(1)] window,xsize=imsizeout(0),ysize=imsizeout(1), /PIXMAP, /FREE for i=0,len-1 do begin coordu=coord & cyu=cy & cxu=cx if keyword_set(abmovie) then begin dt=where(detectors eq dets(i),cnt) if cnt gt 0 then if scv(dt(0)) eq strupcase(abmovie) then begin coordu=coord2 & cyu=cy2 & cxu=cx2 endif endif erase,0 if keyword_set(usemask) then umsk=usemask(i) else begin dt=where(detectors eq dets(i),cnt) if cnt gt 0 then umsk=outer(dt(0)) endelse if umsk eq 0 then masks(i,*,*)=255 if umsk gt 0 then begin !x.crange=[0,0] wcs=(*wcsptr[i]) pixsize=(xminmax(1)-xminmax(0))/hsize if ~keyword_set(maskindeg) then maskr=((180/!pi)*1000*onersun()/wcs.position.dsun_obs)*(umsk/pixsize) else maskr=umsk/pixsize tvcircle,maskr,cxu,cyu,255,/fill masks(i,*,*)=tvrd() endif endfor wdel,!d.window select_windows endif else begin if ~(islog) then elong=replicate(1,imsizeout[1])##lgen(imsizeout[0],yminmax) else elong=replicate(1,imsizeout[1])##(10^lgen(imsizeout[0],alog10(yminmax))) pa=lgen(imsizeout[1],xminmax)##replicate(1,imsizeout[0]) coord[0,*,*]=elong coord[1,*,*]=pa cx=coord[0,0,0] & cy=coord[1,0,0] for i=0,len-1 do begin if keyword_set(usemask) then begin umsk=usemask(i) cnt=1 endif else begin ; dt=where(detectors eq dets(i) and strpos(dets(i),'HI') eq -1,cnt) dt=where(detectors eq dets(i),cnt) if cnt gt 0 then umsk=outer(dt(0)) endelse if ~keyword_set(maskindeg) then umsk=((180/!pi)*1000*onersun()/wcs.position.dsun_obs)*umsk if cnt gt 0 then sm=where(coord(0,*,*) le umsk ,cnt) if cnt gt 0 and umsk gt 0 then begin tmp=reform(masks(i,*,*)) tmp(sm)=255 masks(i,*,*)=tmp endif else masks(i,*,*)=255 endfor coord=heliorad2heliocart(reverse(coord,1)) endelse if keyword_set(fmask) then begin if keyword_set(usemask) then fmk=where(usemask eq -1,cnt) else fmk=where(outer eq -1,cnt) for i2=0,cnt-1 do begin i=fmk(i2) if keyword_set(usemask) then umsk=usemask(i) else begin dt=where(detectors eq dets(i),cnt) if cnt gt 0 then umsk=outer(dt(0)) endelse if umsk eq -1 and fmask(i) ne '' then begin wcs=(*wcsptr[i]) mskim=rebin(sccreadfits(fmask(i),mhdr),wcs.naxis(0),wcs.naxis(1)) if keyword_set(abmovie) and scv(i) eq strupcase(abmovie) then coordu=coord2 else coordu=coord if wcs.cunit(0) eq 'arcsec' then coords=coordu*3600. else coords=coordu pixel=wcs_get_pixel(wcs,coords,/force_proj) mskim=reform(interpolate(float(mskim),pixel[0,*,*],pixel[1,*,*],cubic=-0.5,missing=-32000.)) mskim(where(mskim gt 0))=255 mskim(where(mskim le 0))=0 masks(i,*,*)=mskim endif endfor endif ; ---- init output image red image rimo and rimo2 for abmovies are used to create a grayscale frame rimo=bytarr(imsizeout(0),imsizeout(1)) imo=bytarr(imsizeout(0),imsizeout(1)) ;if truecolor ne 1 then imo=make_array(dim=imsizeout,/float) else begin if truecolor eq 1 then begin imo=bytarr(3,imsizeout(0),imsizeout(1)) rimo=bytarr(imsizeout(0),imsizeout(1)) gimo=bytarr(imsizeout(0),imsizeout(1)) bimo=bytarr(imsizeout(0),imsizeout(1)) endif if keyword_set(abmovie) then begin rimo2=bytarr(imsizeout(0),imsizeout(1)) if truecolor eq 1 then begin imo=bytarr(3,(imsizeout(0)*2)+2,imsizeout(1)) rimo2=bytarr(imsizeout(0),imsizeout(1)) gimo2=bytarr(imsizeout(0),imsizeout(1)) bimo2=bytarr(imsizeout(0),imsizeout(1)) endif endif ; endelse ; ---- init mvi hdr def_mvi_hdr,cfile_hdr if rtheta ne 0 then cfile_hdr.RTHETA = 4 + rtheta else cfile_hdr.RTHETA = rtheta cfile_hdr.RADIUS0 = yminmax(0) cfile_hdr.RADIUS1 = yminmax(1) cfile_hdr.THETA0 = xminmax(0) cfile_hdr.THETA1 = xminmax(1) cfile_hdr.sunxcen=cx ;RADIUS0 pixel cfile_hdr.sunycen=cy ;THETA0 pixel if keyword_set(abmovie) then cfile_hdr.nx=(imsizeout(0)*2)+2 else cfile_hdr.nx=imsizeout(0) cfile_hdr.ny=imsizeout(1) cfile_hdr.nf=1 cfile_hdr.sec_pix=((xminmax(1)-xminmax(0))/imsizeout(0)) ;deg cfile_hdr.truecolor=truecolor if datatype(pngvar) eq 'STC' then begin if pngvar.mvtype eq 1 then begin pngvar.x0=cfile_hdr.THETA0 & pngvar.x1=cfile_hdr.THETA1 & pngvar.y0=cfile_hdr.RADIUS0 & pngvar.y1=cfile_hdr.RADIUS1 endif else begin pngvar.x0=cfile_hdr.RADIUS0 & pngvar.x1=cfile_hdr.RADIUS1 & pngvar.y0=cfile_hdr.THETA0 & pngvar.y1=cfile_hdr.THETA1 endelse WIDGET_CONTROL, pngvar.x0v, SET_VALUE=string(pngvar.x0,'(F6.2)') WIDGET_CONTROL, pngvar.x1v, SET_VALUE=string(pngvar.x1,'(F6.2)') WIDGET_CONTROL, pngvar.y0v, SET_VALUE=string(pngvar.y0,'(F6.2)') WIDGET_CONTROL, pngvar.y1v, SET_VALUE=string(pngvar.y1,'(F6.2)') endif endif else cfile_hdr.nf=cfile_hdr.nf+1 ;stop if truecolor ne 1 then rimo=rimo*0 else begin imo=imo*0 & rimo=rimo*0 & gimo=gimo*0 & bimo=bimo*0 endelse if keyword_set(bkgclr) and truecolor ne 1 then rimo=rimo+bkgclr if keyword_set(bkgclr) and truecolor eq 1 then begin rimo(*,*)=bkgclr(0) gimo(*,*)=bkgclr(1) bimo(*,*)=bkgclr(2) endif if keyword_set(abmovie) then begin if truecolor ne 1 then rimo2=rimo2*0 if truecolor eq 1 then begin rimo2=rimo2*0 & gimo2=gimo2*0 & bimo2=bimo2*0 endif if keyword_set(bkgclr) and truecolor ne 1 then rimo2=rimo2+bkgclr if keyword_set(bkgclr) and truecolor eq 1 then begin rimo2(*,*)=bkgclr(0) gimo2(*,*)=bkgclr(1) bimo2(*,*)=bkgclr(2) endif endif ;create frame header from largest pix size image io=wcsorder(0) if datatype(files) eq 'STR' then begin BREAK_FILE, files(io), a, dir, name, ext2, /last if ext2 EQ '.fts' then img=sccreadfits(files(io),frame_hdr,/nodata) else begin parse_secchi_filename, name, dobs, det, sc, wvl, cname frame_hdr.filename=cname+ext2 frame_hdr.detector=det frame_hdr.wavelnth = wvl frame_hdr.date_obs=strmid(dobs,0,10) frame_hdr.time_obs=strmid(dobs,11,8) frame_hdr.roll = 0. endelse endif else begin frame_hdr=(*hdrs[io]) endelse if keyword_set(frametime)then begin frame_hdr.date_obs=strmid(frametime,0,10) frame_hdr.time_obs=strmid(frametime,11,8) endif if keyword_set(abmovie) then osc =strupcase(abmovie) else osc='na' for i2=0,len-1 do begin i=wcsorder(i2) if datatype(files) eq 'STR' then begin BREAK_FILE, files(i), a, dir, name, ext2, /last if strpos(files(i),'http') eq 0 then begin uname=getenv('HOME')+'/tmp'+ext2 sock_get,files(i),uname endif else uname=files(i) if ext2 EQ '.png' then img = READ_PNG(uname,r,g,b) if ext2 EQ '.gif' then READ_GIF,uname,img,r,g,b if ext2 EQ '.jpg' then begin READ_JPEG, uname, img, clrtable, COLORS=!D.N_COLORS-1,/TWO_PASS_QUANTIZE,DITHER=1,/grayscale r=clrtable(*,0) & g=clrtable(*,1) & b=clrtable(*,2) endif if ext2 EQ '.fts' then begin img=readfits(files(i),fhdr) img=bytscl(img) endif endif else img=(*files[i]) if keyword_set(ctable) then begin nc1=i2*256 & nc2=((i2+1)*256)-1 r=ctable(nc1:nc2,0) g=ctable(nc1:nc2,1) b=ctable(nc1:nc2,2) endif wcs=(*wcsptr[i]) coordu=coord & scvu='' if keyword_set(abmovie) then begin dt=where(detectors eq dets(i),cnt) if cnt gt 0 then if scv(dt(0)) eq strupcase(abmovie) then begin scvu=scv(dt(0)) coordu=coord2 endif endif if wcs.cunit(0) eq 'arcsec' then coords=coordu*3600. else coords=coordu pixel=wcs_get_pixel(wcs,coords,/force_proj) print,'Interpolating image...' ; imotmp=reform(interpolate(float(img),pixel[0,*,*],pixel[1,*,*],cubic=-0.5,missing=-32000.)) imotmp=reform(interpolate(float(img),pixel[0,*,*],pixel[1,*,*],missing=-32000.)) tmp=reform(masks(i,*,*)) if i2 gt 0 or keyword_set(usemask) then mok=where(imotmp ne -32000. and tmp eq 255) else mok=where(imotmp ne -32000.) ; if i2 gt 0 or keyword_set(usemask) then mok=where(imotmp ne 0 and tmp eq 255) else mok=where(imotmp ne 0) if keyword_set(abmovie) and i2 le 1 and ~keyword_set(usemask) then mok=where(imotmp ne -32000.);dont add mask for outer image on abmovie if mok(0) gt -1 and truecolor ne 1 then begin if osc eq scvu then rimo2[mok]=byte(imotmp[mok]) else rimo[mok]=byte(imotmp[mok]) endif if mok(0) gt -1 and truecolor eq 1 and osc ne scvu then begin rimo[mok]=r(imotmp[mok]) gimo[mok]=g(imotmp[mok]) bimo[mok]=b(imotmp[mok]) endif if mok(0) gt -1 and truecolor eq 1 and osc eq scvu then begin rimo2[mok]=r(imotmp[mok]) gimo2[mok]=g(imotmp[mok]) bimo2[mok]=b(imotmp[mok]) endif endfor if truecolor ne 1 then begin if keyword_set(abmovie)then begin divider=bytarr(2,imsizeout(1)) imo=[rimo,divider,rimo2] endif else imo=rimo endif if truecolor eq 1 then begin if ~keyword_set(abmovie) then begin imo(0,*,*)=rimo imo(1,*,*)=gimo imo(2,*,*)=bimo endif else begin divider=bytarr(2,imsizeout(1)) rimot=[rimo,divider,rimo2] gimot=[gimo,divider,gimo2] bimot=[bimo,divider,bimo2] imo(0,*,*)=rimot imo(1,*,*)=gimot imo(2,*,*)=bimot endelse endif imo=byte(imo) if datatype(ext2) ne 'UND' then if uname eq getenv('HOME')+'/tmp'+ext2 then file_delete,uname file_hdr=cfile_hdr help,imo return,imo end