;+ ; $Id: jmap_in_situ.pro,v 1.2 2011/04/28 20:03:15 nathan Exp $ ; ;PRO jmap_in_situ ; ; present jmap and insitu data together ; ;INPUT: jmapfile name of the jmap file which is to be used ; ;KEYWORDS: getang show in a dialog box the recommended position angle to use ; ;METHOD: Ask for date if not given, then gives approximate PA to use. Plot jmap, after sat selected, ; use draw_insitu to draw the elongation fo the insitu sat, and read in all of the data, only plot v and dens. ; When clicked on, plot a theoretical height time curve of an event intersecting the insitu satellite at the ; chosen date. Zoom in around selected events to plot the rest of the parameters ; ;SYNTAX: jmap_in_situ,jmapfile,getang=getang ; ;Can also be called from tool2a.pro ; ;CALLS: read_is.pro, various spice functions ; ; RESTRICTIONS: $INSITU_PATH must be defined as the location of the in-situ data to be read in: ; $INSITU_PATH/ACE ; ;- ; $Log: jmap_in_situ.pro,v $ ; Revision 1.2 2011/04/28 20:03:15 nathan ; add comments ; ; Revision 1.1 2010/06/29 15:28:06 cooper ; Version 1 ; ; ;event handler for the menu for selecting various options while running gui ;IF insitu sat selected,draw its elongation, give approx delta, plot v and dens PRO menu_event, event COMMON shared,is_loc,instructions,hdr,xsize,ysize,xstart,date,data,magdata,jmap,beta,$ label,is,zoomtime,image_id,plot_id,syncpoint,plotstruct,istrack,loaddir,base0,settings,printbase,printsettings widget_control,event.id,get_uvalue=uval IF datatype(uval) NE 'STR' THEN uval='' IF uval eq 'buttons' THEN uval=event.value CASE uval of 'sta':BEGIN is_loc='A' & is='ST_A' & END 'stb':BEGIN is_loc='B' & is='ST_B' & END 'omni':BEGIN is_loc='Earth' & is='OMNI' & END 'ace':BEGIN is_loc='Earth' & is='ACE' & END 'wind':BEGIN is_loc='Earth' & is='WIND' & END 'mes':BEGIN is_loc='Mercury' & is='MESSENGER' & m=dialog_message('Not implemented') & draw_insitu & redisp &return & END 've':BEGIN is_loc='Venus' & is='VENUS_EXPRESS' & m=dialog_message('Not implemented') & draw_insitu & redisp &return & END 'soho':BEGIN is_loc='Earth' & m=dialog_message('Not implemented') &return & END 'quit':BEGIN und widget_control,base0,/destroy END 'print':printplots 'load': BEGIN wset,image_id jmapfile=dialog_pickfile(title='Load jMap', path=loaddir, filter='*.jmp',get_path=loaddir) IF jmapfile NE '' THEN BEGIN IF datatype(plot_id) NE 'UND' THEN BEGIN wset,plot_id wdelete undefine,plot_id wset,image_id ENDIF erase und jmap=read_jmap2a(jmapfile,header=hdr) loadct,0,/silent jmap=congrid(jmap,xsize,ysize) tvscl, jmap, xstart,0 ;plot the jmap date=hdr.start_time+(hdr.start_time-hdr.end_time)/2. widget_control,instructions,set_value='Select the in-situ spacecraft' ENDIF END 'sync': BEGIN IF file_test(concat_dir(getenv('HOME'),'syncjmapwithmovie.dat')) THEN BEGIN temp=fltarr(3) OPENR,lun,concat_dir(getenv('HOME'),'syncjmapwithmovie.dat'),/get_lun READF,lun,temp free_lun,lun IF (temp[2]-hdr.pa GT 6) THEN mess=dialog_message('Point is more than 6 degrees'+$ 'away from jmap',/error)$ ELSE BEGIN time=(temp[0]-hdr.start_time)*xsize/(hdr.end_time-hdr.start_time)+xstart height=(temp[1]-hdr.min_r)*ysize/(hdr.max_r-hdr.min_r) syncpoint={time:time,height:height,posang:hdr.pa} redisp ENDELSE ENDIF END ELSE: ENDCASE SWITCH uval of 'text': BEGIN stage=2 & break & END 'sta': 'stb': 'omni': 'ace': 'mes': 've': 'wind': 'soho': stage=1 ENDSWITCH IF datatype(stage) EQ 'UND' THEN stage=0 IF stage eq 1 THEN BEGIN WIDGET_CONTROL,settings.getace,get_value=getace getace=getace[0] WIDGET_CONTROL,settings.coord,get_value=coord WIDGET_CONTROL,zoomtime,sensitive=0 wset,image_id undefine,plotstruct draw_insitu erase redisp widget_control,instructions,set_value='Reading the in-situ data...' records=read_is(is,hdr.start_time,hdr.end_time,getace=getace,gsm=coord) blank=replicate(' ',12) data=records.data magdata=records.magdata times=data[0,*] vels=data[1,*] dens=data[2,*] loadct,12,/silent plot, times, vels, ystyle=20,xstyle=1,color=255,/noerase,/nodata,position=[0.04/1.08,0.8,(1.-0.04/1.08),0.99],$ xminor=1,xtickname=blank axis,yaxis=0,/save,yrange=[min(vels),max(vels)],ytitle='Velocity',ystyle=16,yminor=1,color=200 oplot,times,vels,color=200 axis,yaxis=1,/save,yrange=[min(dens),max(dens)],ytitle='Density',ystyle=16,yminor=1 oplot,times,dens,color=255 widget_control,instructions,set_value='Click on either the intersection, or the time of maximum density increase' ENDIF IF stage eq 2 THEN BEGIN widget_control,zoomtime,get_value=timeint timeint=float(timeint[0]) zoom,timeint ENDIF END ;calculates the elongation(using spice) of the insitu spacecraft on the jmap ;for nonstereo spacecraft, actually finds elongation of planet they are to orbit ;returns a 2 dimensional array of times and elongations, in pixels PRO draw_insitu COMMON shared IF (hdr.pa GE 0 AND hdr.pa LE 179) THEN sat='A' ELSE sat='B' n=30. ;calculate 30 different elongs for it s=hdr.start_time e=hdr.end_time interval=(e-s)/n times=dblarr(n+1) times+=s+indgen(n+1)*interval times=[times] ob_info=get_stereo_lonlat(times,sat) ob_rot=get_stereo_carr_rot(times,sat) is_info=get_stereo_lonlat(times,is_loc) is_rot=get_stereo_carr_rot(times,is_loc) IF sat EQ 'A' THEN sep=is_rot-ob_rot ELSE sep=ob_rot-is_rot sep*=2*!pi ;A looks left, B looks right ;sep is separation between carrington rotations (beta) rho=transpose(is_info[0,*]/ob_info[0,*]) alpha=atan([rho*sin(sep)]/[1-rho*cos(sep)])*180./!pi alphap=(alpha-hdr.min_r)*ysize/(hdr.max_r-hdr.min_r) ;alpha in pixels times=(times-hdr.start_time)*xsize/(hdr.end_time-hdr.start_time) istrack=[[times],[alphap]] END ;event handler for the draw widget ;for each event, first convert date from device coords to tai ;for a motion event at any time, get date and elong of mouse, put in bottom label ;Left click plots PRO jmap_event,ev COMMON shared d=ev.x start_t=hdr.start_time end_t=hdr.end_time tscale=(end_t-start_t)/xsize d=(d-xstart)*tscale+start_t ;date in tai elong=ev.y e_scale=(hdr.max_r-hdr.min_r)/ysize elong=elong*e_scale+hdr.min_r IF ev.press EQ 0 and ev.release EQ 0 THEN BEGIN ;motion event, get date and elong IF d GT end_t or d LT start_t THEN return IF elong LT hdr.min_r or elong GT hdr.max_r THEN elong='Out of range' If datatype(beta) NE 'UND' THEN widget_control,label,set_value='PA: '+strtrim(hdr.pa,2)+$ ' Date: ' + anytim2utc(d,/vms) +' Elongation: '$ + strtrim(elong,2)+' Beta:' +strtrim(round(beta*180./!pi),2)$ ELSE widget_control,label,set_value='PA: '+strtrim(hdr.pa,2)+' Date: ' + anytim2utc(d,/vms)+$ ' Elongation: '+ strtrim(elong,2) ENDIF IF ev.press EQ 0 THEN return;no button release events IF ev.press EQ 2 THEN begin;middle button for syncing time=ev.x height=ev.y posang=hdr.pa syncpoint={time:time,height:height,posang:posang} sav_point=[d,elong,posang] OPENW,lun,concat_dir(getenv('HOME'),'syncjmapwithmovie.dat'),/get_lun printf,lun,sav_point free_lun,lun ENDIF IF ev.press EQ 1 AND datatype(data) NE 'UND' THEN begin ;right click to plot theoretical ht curve IF(ev.x LT xstart AND ev.x GT xstart+xsize) THEN return ;dont change unless jmap or graph clicked on date=d IF datatype(plot_id) NE 'UND' THEN BEGIN wset,plot_id wdelete wset,image_id undefine,plot_id ENDIF IF (hdr.pa GE 0 AND hdr.pa LE 179) THEN sat='A' ELSE sat='B' ;find alpha for the sc at this given date is_rot=get_stereo_carr_rot(date,is_loc) is_info=get_stereo_lonlat(date,is_loc) ob_rot=get_stereo_carr_rot(date,sat) ob_info=get_stereo_lonlat(date,sat) a=ob_info[0] r=is_info[0] rho=r/a beta=abs(is_rot-ob_rot)*2*!pi is_alpha=atan((rho*sin(beta))/(1-rho*cos(beta)))*180./!pi ;dates in data file will not match time exactly, take a weighted average of the ;velocities of the two nearest times t_close1=min(data[0,*]-date,t1,/absolute) IF t_close1 lt 0 THEN t2=t1+1 ELSE t2=t1-1 t_close2=data[0,t2] t_close1+=date weight1=1-abs(date-t_close1)/abs(t_close1-t_close2) weight2=1-abs(date-t_close2)/abs(t_close1-t_close2) v=weight1*data[1,t1] +weight2*data[1,t2];this is the weighted average rhos=rho+v*(data[0,*]-date)/a ;calculate trajectory alphas=atan(rhos*sin(beta)/(1-rhos*cos(beta)))*180/!pi locs=where(alphas gt 4. AND alphas lt 60>is_alpha+7<85) alphas=alphas[locs] times=data[0,locs] plotstruct={alpha:alphas,times:times,d:d} widget_control,instructions,set_value='Enter a time interval into the text box to plot zoom in around the selected event. Default is 2 days' widget_control,zoomtime,/sensitive widget_control,zoomtime,set_value='2' ENDIF redisp END ;displays everything PRO redisp COMMON shared wset,image_id loadct,0,/silent tvscl,jmap,xstart,0 ;draw the jmap IF datatype(syncpoint) NE 'UND' THEN BEGIN ;show syncpoint if there is one XYOUTS,syncpoint.time,syncpoint.height-1,')]',alignment=0,color=0,/device XYOUTS,syncpoint.time,syncpoint.height-1,'[(',alignment=1,color=255,/device ENDIF loadct,4,/silent IF datatype(istrack) NE 'UND' THEN BEGIN ;draw the track of the insitu spacecraft times=istrack[*,0] alphas=istrack[*,1] plot,times,alphas,/device,thick=3,color=240,xstyle=5,ystyle=5,/noerase,$ position=[xstart,0,xstart+xsize,ysize],xrange=[0,xsize],yrange=[0,ysize] ENDIF IF datatype(plotstruct) NE 'UND' THEN BEGIN ;draw the theoretical ht curve plot,[hdr.start_time,hdr.end_time],[hdr.min_r,hdr.max_r],xstyle=1,ystyle=17,/nodata,$ /noerase,position=[xstart,0,xstart+xsize,ysize],/device oplot,plotstruct.times,plotstruct.alpha,color=240,thick=2.5 oplot,[plotstruct.d,plotstruct.d],[hdr.min_r,hdr.max_r],color=240,thick=2 ;vertical line through date ENDIF END ;plots data zoomed in a few days around the events ;data is in the format of a structure with 2 arrays, data and magdata PRO zoom,timeint COMMON shared zstart=date-timeint*86400D;;86400s=1 day zend=date+timeint*86400D ; z_where=where(data[0,*] GE zstart and data[0,*] LE zend and data[3,*] GT 0) ;indices for zoom in ztimes=data[0,z_where] zvels=data[1,z_where] zdens=data[2,z_where] ztemps=data[3,z_where] m_where=where(magdata[0,*] GE zstart and magdata[0,*] LE zend) mtimes=magdata[0,m_where] mtotal=magdata[1,m_where] mtheta=magdata[2,m_where] mphi=magdata[3,m_where] mbeta=magdata[4,m_where] window,xsize=700,ysize=400,ypos=0 device,cursor_standard=2 plot_id=!d.window blank=replicate(' ',12) loadct,12,/silent trange=[min(ztimes),max(ztimes)] ;make sure mag and epam plots use same time range,to line things up plot,ztimes,zvels,ystyle=20,xstyle=5+8,background=255,color=0,/nodata,$ position=[0.1,0.7,0.9,0.9];,xtickunits='Days', ;dummy=label_dates tjul=cds2jd(anytim2utc(ztimes)) tjul=tjul.int+tjul.frac axis,xaxis=1,xrange=[min(tjul),max(tjul)],xtickunits='day',xstyle=1,xminor=4,color=0 axis,yaxis=0,/save,yrange=[min(data[1,*]),max(data[1,*])],ytitle='Velocity',ystyle=16,$ yminor=1,color=200 oplot,ztimes,zvels,color=200 ;velocity axis,yaxis=1,/save,yrange=[min(data[2,*]),max(data[2,*])],ytitle='Density',yminor=1,color=0,ystyle=16 oplot,ztimes,zdens,color=0 ;density zwhere=where(ztemps GT 1000) plot,ztimes[zwhere],ztemps[zwhere],/noerase,color=0,position=[0.1,0.2,0.9,0.3],/ylog,xstyle=1,xtickname=blank,$ ystyle=1,yminor=1,ytitle='T(K)';temp,log plot,mtimes,mtotal,/noerase,color=0,position=[0.1,0.5,0.9,0.7],xstyle=1,xtickname=blank,ystyle=1,$ ytitle='B',yminor=1,yticks=1,ytickv=[round(max(mtotal)/2)],xrange=trange ;mag field b plot,mtimes,mphi,/noerase,color=0,position=[0.1,0.4,0.9,0.5],xstyle=1,xtickname=blank,ystyle=1,$ ytitle='phi',yminor=1,yticks=1,ytickv=[180],xrange=trange;phi (long of b) plot,mtimes,mtheta,/noerase,color=0,position=[0.1,0.3,0.9,0.4],xstyle=1,xtickname=blank,ystyle=1,$ ytitle='theta',yminor=1,yticks=2,ytickv=[45,-45],xrange=trange;theta (lat of b) bwhere=where(mbeta GT 0 AND mbeta LT 10.^5) ;need to do this because beta may be calculated before bad data removed plot,mtimes[bwhere],mbeta[bwhere],/noerase,color=0,position=[0.1,0.1,0.9,0.2],/ylog,xstyle=1,xtickname=blank,$ yminor=1,xrange=trange,yticks=1,ytickv=[10,1],ytitle='beta' oplot,[min(mtimes),max(mtimes)],[1,1],color=30 ;horizontal line through beta=1 plot,ztimes,[0,1],ystyle=5,xstyle=5,/nodata,position=[0.1,0.1,0.9,0.9],/noerase oplot,[date,date],[0,1],color=100 ;vertical line through the date END PRO print_event,event Widget_control,event.top,get_uvalue=info CASE event.ID OF info.cancelb:widget_control,event.top,/destroy info.printb:BEGIN temp=widget_info(info.printerb,/combobox_gettext);the name of the printer (*info.infoptr).printer=temp widget_control,info.pageb,get_value=temp ;2-dim boolean array, [print jmap,print plots] (*info.infoptr).pages=temp (*info.infoptr).cancel=0 widget_control,event.top,/destroy END ELSE: ENDCASE END PRO printplots COMMON shared IF datatype(plot_id) EQ 'UND' THEN BEGIN mess=dialog_message('Not ready to print...',/error) return ENDIF spawn,'lpstat -a',printers;get the names of the printers FOR i=0,n_elements(printers)-1 DO BEGIN printers[i]=strmid(printers[i],0,strpos(printers[i],' accepting')) ENDFOR printbase=WIDGET_BASE(column=1,/base_align_center,title='Print Settings',group_leader=base0,/modal) lbl=WIDGET_LABEL(printbase,value='Select A Printer') printer=WIDGET_COMBOBOX(printbase,value=printers,/dynamic_resize) page=CW_Bgroup(printbase,['jMap','Plots'],/nonexclusive,row=1,label_top='Print which page(s)?',set_value=[1,1]) buttonbase=WIDGET_BASE(printbase,row=1) printb=Widget_button(buttonbase,value='Print') cancelb=widget_button(buttonbase,value='Cancel') widget_control,printbase,/realize infoptr=ptr_new({cancel:1,pages:[1,1],printer:''}) info={printb:printb,printerb:printer,pageb:page,cancelb:cancelb,infoptr:infoptr} widget_control,printbase,set_uvalue=info xmanager,'print',printbase IF (*infoptr).cancel EQ 1 THEN return p=+(*infoptr).printer pages=(*infoptr).pages ptr_free,infoptr IF pages[0] NE 0 THEN BEGIN wset,image_id loadct,0,/silent image1=tvrd(.04*xsize,0,xsize,ysize,true=1) ENDIF IF pages[1] NE 0 THEN BEGIN wset,plot_id image2=tvrd(0,.1*400,true=1) ENDIF filenm=concat_dir(getenv('HOME'),'idl.ps') set_plot,'ps' device,filename=filenm device, xoffset=0, yoffset=0, xsize=8.5, ysize=11, /inches, bits=8, /color IF pages[0] NE 0 THEN BEGIN tvscl,image1,.1,.2,xsize=.75,ysize=.32,true=1,/normal times=data[0,*] vels=data[1,*] dens=data[2,*] loadct,12,/silent t=cds2jd(anytim2utc(times)) tjul=t.int+t.frac blank=replicate(' ',12) plot,times,vels,ystyle=20,xstyle=9,/noerase,/nodata,position=[.1,.52,.85,.72],xminor=1,xtickname=blank axis,xaxis=1,xrange=[min(tjul),max(tjul)],xtickunits='day',xstyle=1,xminor=4 axis,yaxis=0,/save,yrange=[min(vels),max(vels)],ytitle='Velocity',ystyle=16,yminor=1,color=200 oplot,times,vels,color=200 axis,yaxis=1,/save,yrange=[min(dens),max(dens)],ytitle='Density',ystyle=16,yminor=1 oplot,times,dens xyouts, .5,.9,'jMap: '+strtrim(hdr.pa,2)+' Date: '+strmid(anytim2utc(date,/ecs),0,16)+' In Situ: '+is,$ /normal,alignment=0.5 erase ;new page ENDIF IF pages[1] NE 0 THEN BEGIN tvscl,image2,.05,.42,xsize=.9,ysize=.4,true=1,/normal xyouts, .5,.9,'Date: '+strmid(anytim2utc(date,/ecs),0,16)+' In Situ: '+is,$ /normal,alignment=0.5 ENDIF device,/close print,'lp -d '+p+' '+filenm spawn,'lp -d '+p+' '+filenm file_delete,concat_dir(getenv('HOME'),'idl.ps') set_plot,'x' END PRO und ;undefine things in common block, when needed COMMON shared undefine,syncpoint & undefine,data & undefine,magdata & undefine,beta &undefine,plotstruct &$ undefine,istrack & undefine,plot_id & undefine,jmap END ;load in jmap, make widget, PRO jmap_in_situ, jmapfile, getang=getang COMMON shared und IF getenv('INSITU_PATH') EQ '' THEN message,'The environment variable INSITU_PATH must be defined as the location to which insitu data files are stored' IF datatype(jmapfile) EQ 'UND' THEN BEGIN date='' ;get the date and satellite to be used to figure out which position angle read,'Enter a date (YYYY-MM-DD): ',date sat='' read,'Which satellite (A/B): ',sat pa=get_ecliptic_pa(date,sat) print,'Recommended position angle (position angle of ecliptic)='+strmid(strtrim(pa,2),0,5) date=anytim2utc(date,/vms) month=strlowcase(strmid(date,3,3)) yr=strmid(date,9,2) jmap_dir='/sjmaps'+yr+'/'+month jmapfile=dialog_pickfile(title='Load jMap', path=jmap_dir, filter='*.jmp',get_path=loaddir) ENDIF base0=WIDGET_BASE(TITLE='jMAP/data',column=2) base=WIDGET_BASE(base0,TITLE='jMap/data',uvalue='base',column=1,frame=6) jmap=read_jmap2a(jmapfile,header=hdr) xsize=hdr.nx<1024 ysize=hdr.ny<512 instructions=WIDGET_LABEL(base,uvalue='instruct',value='Select the in-situ spacecraft',/align_center,xsize=xsize) image=WIDGET_DRAW(base,uvalue='jmp', xsize=1.08*xsize, ysize=1.3*ysize,/button_events,/motion_events) label=WIDGET_LABEL(base,xsize=xsize-50,/align_center,value=' ') widget_control,base0,/realize widget_control,image,get_value=image_id jmap=congrid(jmap,xsize,ysize) wset,image_id device,cursor_standard=33 loadct, 0, /silent xstart=0.04*xsize xend=xstart+xsize tvscl, jmap, xstart,0 ;plot the jmap date=hdr.start_time+(hdr.start_time-hdr.end_time)/2. ;initially make date halfway between start and end IF keyword_set(getang) THEN BEGIN IF (hdr.pa GE 0 AND hdr.pa LE 179) THEN sat='A' ELSE sat='B' pa=get_ecliptic_pa(date,sat) mess=dialog_message('Recommended position angle (pa of ecliptic)='+strmid(strtrim(pa,2),0,5),/information) ENDIF menu=WIDGET_BASE(base0,column=1,/base_align_center,ypad=5,frame=6,space=30) minibase=WIDGET_BASE(menu,frame=3,column=1) temp=widget_label(minibase,value='In-Situ Sats',/align_center) satnames=['Stereo A','Stereo B','OMNI','ACE','WIND','Messenger','Venus Express','CELIAS'] tempuval=['sta','stb','omni','ace','wind','mes','ve','soho'] sats=CW_BGROUP(minibase,satnames,button_uvalue=tempuval,column=1,uvalue='buttons',frame=3) minibase=WIDGET_BASE(menu,frame=3,column=1,/align_center) temp=widget_label(minibase,value='Plots Time Interval',/align_center) zoomtime=widget_text(minibase,value='2',/editable,uvalue='text',sensitive=0,frame=3) minibase=WIDGET_BASE(menu,frame=3,column=1,/base_align_center) temp=WIDGET_label(minibase,value='Settings') getace=CW_Bgroup(minibase,['Use get_acedata'],/nonexclusive,row=1) coord=CW_Bgroup(minibase,['GSE','GSM'],/exclusive,row=1,label_top='OMNI/WIND B Coord System',set_value=0) settings={getace:getace,coord:coord} minibase=WIDGET_BASE(menu,frame=3,column=1) optnames=['Sync','Load New','Print','Quit'] tempuval=['sync','load','print','quit'] temp=widget_label(minibase,value='Options',/align_center) opts=CW_BGROUP(minibase,optnames,button_uvalue=tempuval,column=2,frame=3,uvalue='buttons') xmanager,'jmap',base,/just_reg xmanager,'menu',menu END