;$Author: nikos $ ;$Date: 2015-06-12 10:48:10 -0700 (Fri, 12 Jun 2015) $ ;$Header: /home/rumba/cdaweb/dev/control/RCS/spd_cdawlib_virtual_funcs.pro,v 1.0 ;$Locker: kovalick $ ;$Revision: 17856 $ ; ;Copyright 1996-2013 United States Government as represented by the ;Administrator of the National Aeronautics and Space Administration. ;All Rights Reserved. ; ;------------------------------------------------------------------ compile_opt idl2 ;+ ; ; NAME: Function VTYPE_NAMES ; ; PURPOSE: Returns array of names or index numbers where the var_type is ; equal to vtype (eg."data"). ; function vtype_names, buf, vtype, NAMES=vNAMES tagnames = tag_names(buf) tagnums = n_tags(buf) vnames=strarr(tagnums) vindices=intarr(tagnums) ; Determine names and indices ii=0 for i=0, tagnums-1 do begin tagnames1=tag_names(buf.(i)) if(spd_cdawlib_tagindex('VAR_TYPE', tagnames1) ge 0) then begin if(buf.(i).VAR_TYPE eq vtype) then begin ;if(buf.(i).VAR_TYPE eq 'data') then begin vnames[ii]=tagnames[i] vindices(ii)=i ii=ii+1 endif endif endfor wc=where(vnames ne '',wcn) if(wc[0] lt 0) then begin vnames[0]=wc vindices[0]=wc endif else begin vnames=vnames[wc] vindices=vindices[wc] endelse ;Jan. 6, 2003 - TJK added the "or (n_elements..." below because in IDL 5.6 ;if the NAMES keyword is set as "" in the calling routine, IDL doesn't think ;the keyword is set (as it does in previous IDL versions). ;if(keyword_set(NAMES) or (n_elements(names) gt 0)) then begin ; NAMES=vnames ;endif return, vindices end ;+ ; ; NAME: Function Trap ; ; PURPOSE: Trap malformed idl structures or invalid arguments. ; ; INPUT; a an idl structure function buf_trap, a ibad=0 str_tst=size(a) if(str_tst(str_tst[0]+1) ne 8) then begin ibad=1 v_data='DATASET=UNDEFINED' v_err='ERROR=a'+strtrim(string(i),2)+' not a structure.' v_stat='STATUS=Cannot plot this data' a=create_struct('DATASET',v_data,'ERROR',v_err,'STATUS',v_stat) endif else begin ; Test for errors trapped in conv_map_image atags=tag_names(a) rflag=spd_cdawlib_tagindex('DATASET',atags) if(rflag[0] ne -1) then ibad=1 endelse return, ibad end ;+ ; ; NAME: Function VV_NAMES ; ; PURPOSE: Returns array of virtual variable names or index numbers. ; function vv_names, buf, NAMES=NAMES tagnames = tag_names(buf) tagnums = n_tags(buf) vnames=strarr(tagnums) vindices=intarr(tagnums) ; Determine names and indices ii=0 for i=0, tagnums-1 do begin tagnames1=tag_names(buf.(i)) if(spd_cdawlib_tagindex('VIRTUAL', tagnames1) ge 0) then begin if(buf.(i).VIRTUAL) then begin vnames[ii]=tagnames[i] vindices[ii]=i ii=ii+1 endif endif endfor wc=where(vnames ne '',wcn) if(wc[0] lt 0) then begin vnames[0]=wc vindices[0]=wc endif else begin vnames=vnames[wc] vindices=vindices[wc] endelse ;TJK IDL6.1 doesn't recognize this keyword as being set since ;its defined as a strarr(1)... ;if(keyword_set(NAMES)) then NAMES=vnames if(n_elements(NAMES)) then begin NAMES=vnames endif return, vindices end ;----------------------------------------------------------------------------- ;+ ; NAME: Function CHECK_MYVARTYPE ; ; PURPOSE: ; Check that all variables in the original variable list are declared as ; data otherwise set to ignore_data ; Find variables w/ var_type == data ; ; CALLING SEQUENCE: ; ; status = check_myvartype(buf,org_names) ; ; VARIABLES: ; ; Input: ; buf - an IDL structure built w/in spd_cdawlib_read_mycdf ; org_names - list of original variables input to spd_cdawlib_read_mycdf. Any ; variables in this list will remain tagged as ; VAR_TYPE= data otherwise VAR_TYPE = metadata. ; ; Output: ; buf - an IDL structure containing the populated virtual ; variables ; status - 0 ok else failed ; ; Keyword Parameters: ; ; ; REQUIRED PROCEDURES: ; function check_myvartype, nbuf, org_names status=0 var_names=strarr(1) var_indices = vtype_names(nbuf,'data',NAMES=var_names) if(var_indices[0] lt 0) then begin print, "STATUS= No variable of type DATA detected." print, "ERROR= No var_type=DATA variable found in check_myvartype.pro" print, "ERROR= Message: ",var_indices[0] status = -1 return, status endif org_names=strupcase(org_names) ; RCJ 08/29/2012 Let's find all 'components'. We'll need this list below. compnames=[''] for i=0, n_elements(var_indices)-1 do begin tnames=tag_names(nbuf.(i)) for k=0,n_elements(tnames)-1 do begin pos = strpos(tnames[k],'COMPONENT_') if (pos eq 0) then compnames=[compnames,nbuf.(var_indices[i]).(k)] endfor endfor for i=0, n_elements(var_indices)-1 do begin wc=where(org_names eq var_names[i],wcn) if(wc[0] lt 0) then begin ; this is not the originally requested var. ;print,'***** not requested, make support_data : ',var_names[i] nbuf.(var_indices[i]).var_type = 'support_data' ; wc1=where(strupcase(compnames) eq var_names[i]) if (wc1[0] ne -1) then nbuf.(var_indices[i]).var_type='additional_data' ;if (wc1[0] ne -1) then print,'********** and a component, make additional_data: ',nbuf.(var_indices[i]).varname endif endfor return, status end ;+ ; NAME: Function ALTERNATE_VIEW ; ; PURPOSE: Find virtual variables and replace their data w/ the component0 ; data ; ; CALLING SEQUENCE: ; ; new_buf = alternate_view(buf,org_names) ; ; VARIABLES: ; ; Input: ; ; buf - an IDL structure built w/in spd_cdawlib_read_mycdf ; org_names - list of original variables input to spd_cdawlib_read_mycdf. Any ; variables in this list will remain tagged as ; VAR_TYPE= data otherwise VAR_TYPE = support_data. ; ; Output: ; ; new_buf - an IDL structure containing the populated virtual ; variable ; ; Keyword Parameters: ; ; ; REQUIRED PROCEDURES: ; ; none ; ;------------------------------------------------------------------- ; History ; ; 1.0 R. Baldwin HSTX 1/6/98 ; Initial version ; ;------------------------------------------------------------------- function alternate_view, buf,org_names status=0 ; Establish error handler catch, error_status if(error_status ne 0) then begin print, "ERROR= number: ",error_status," in alternate_view" print, "ERROR= Message: ",!ERR_STRING status = -1 return, status endif ; Find virtual variables vvtag_names=strarr(1) vvtag_indices = vv_names(buf,NAMES=vvtag_names) if(vvtag_indices[0] lt 0) then begin print, "ERROR= No VIRTUAL variable found in alternate_view" print, "ERROR= Message: ",vvtag_indices[0] status = -1 return, status endif tagnames = tag_names(buf) tagnums = n_tags(buf) for i=0, n_elements(vvtag_indices)-1 do begin ; variable_name=arrayof_vvtags(i) ; tag_index = spd_cdawlib_tagindex(variable_name, tagnames) tagnames1=tag_names(buf.(vvtag_indices[i])) ;now look for the COMPONENT_0 attribute tag for this VV. ;TJK had to change to check for 'ge 0', otherwise it wasn't true... if(spd_cdawlib_tagindex('COMPONENT_0', tagnames1) ge 0) then $ component0=buf.(vvtag_indices[i]).COMPONENT_0 ; Check if the component0 variable exists component0_index = spd_cdawlib_tagindex(component0,tagnames) ;print, buf.(vvtag_indices[i]).handle vartags = tag_names(buf.(vvtag_indices[i])) ;11/5/04 - TJK - had to change FUNCTION to FUNCT for IDL6.* compatibility ; findex = spd_cdawlib_tagindex('FUNCTION', vartags) ; find the FUNCTION index number findex = spd_cdawlib_tagindex('FUNCT', vartags) ; find the FUNCTION index number if (findex[0] ne -1) then $ func_name=strlowcase(buf.(vvtag_indices[i]).(findex[0])) ; Loop through all vv's and assign image handle to all w/ 0 handles RTB 12/98 ; Check if handle = 0 and if function = 'alternate_view' if(func_name eq 'alternate_view') then begin ;print, func_name ;print, vvtag_names[i] if(component0_index ge 0) then begin ; WARNING if /NODATASTRUCT keyword not set an error will occur here ;TJK - changed this from tagnames to tagnames1 if(spd_cdawlib_tagindex('HANDLE',tagnames1) ge 0) then begin buf.(vvtag_indices[i]).HANDLE=buf.(component0_index).HANDLE endif else begin print, "Set /NODATASTRUCT keyword in call to spd_cdawlib_read_mycdf" endelse endif else begin print, "ERROR= No COMPONENT0 variable found in alternate_view" print, "ERROR= Message: ",component0_index status = -1 return, status endelse endif ;print, buf.(vvtag_indices[i]).handle endfor ; Check that all variables in the original variable list are declared as ; data otherwise set to support_data ; Find variables w/ var_type == data status = check_myvartype(buf, org_names) return, buf end ;+ ; NAME: Function CROP_IMAGE ; ; PURPOSE: Crop [60,20,*] images into [20,20,*] ; ; CALLING SEQUENCE: ; ; new_buf = crop_image(buf,org_names,index) ; ; VARIABLES: ; ; Input: ; ; buf - an IDL structure built w/in spd_cdawlib_read_mycdf ; org_names - list of original variables input to spd_cdawlib_read_mycdf. Any ; variables in this list will remain tagged as ; VAR_TYPE= data otherwise VAR_TYPE = support_data. ; index - variable index, so we deal with one variable at a time. ; ; Output: ; ; new_buf - an IDL structure containing the populated virtual ; variable ; ; History: Written by RCJ 12/00, based on alternate_view ;- function crop_image, buf, org_names, index=index status=0 ;print, 'In Crop_image' ; Establish error handler catch, error_status if(error_status ne 0) then begin print, "ERROR= number: ",error_status," in crop_image" print, "ERROR= Message: ",!ERR_STRING status = -1 return, status endif tagnames = tag_names(buf) tagnames1=tag_names(buf.(index)) ;now look for the COMPONENT_0 attribute tag for this VV. if(spd_cdawlib_tagindex('COMPONENT_0', tagnames1) ge 0) then $ component0=buf.(index).COMPONENT_0 ; Check if the component0 variable exists component0_index = spd_cdawlib_tagindex(component0,tagnames) ; this line is useful if we are just replacing the old data w/ the new: ;buf.(index).HANDLE=buf.(component0_index).HANDLE ;handle_value,buf.(index).handle,img handle_value,buf.(component0_index).handle,img ; Rick Burley says that from the original 60x20 image ; we need to extract a 20x20 image: buf.(index).handle=handle_create() handle_value,buf.(index).handle,img[19:38,*,*],/set ; ; RCJ 10/22/2003 If the image is being cropped then depend_1 ; should also be cropped. Found this problem when trying to list the data, ; the number of depend_1s did not match the number of data columns. if(spd_cdawlib_tagindex('DEPEND_1', tagnames1) ge 0) then $ depend1=buf.(index).DEPEND_1 ; RCJ 05/16/2013 Good, but if alt_cdaweb_depend_1 exists, use it instead: if(spd_cdawlib_tagindex('ALT_CDAWEB_DEPEND_1', tagnames1) ge 0) then if (buf.(index).alt_cdaweb_depend_1 ne '') then $ depend1=buf.(index).alt_cdaweb_depend_1 ; depend1_index = spd_cdawlib_tagindex(depend1,tagnames) handle_value,buf.(depend1_index).handle,sp ; RCJ 12/29/2003 Check to see if this depend_1 wasn't already cropped ; because of another variable which also uses this var as it's depend_1 if n_elements(sp) gt 20 then $ handle_value,buf.(depend1_index).handle,sp[19:38],/set $ else handle_value,buf.(depend1_index).handle,sp,/set ; no change ; Check that all variables in the original variable list are declared as ; data otherwise set to support_data ; Find variables w/ var_type == data status = check_myvartype(buf, org_names) return, buf end ;+ ; NAME: Function clean_data ; ; pURPOSE: Remove data 3*sigma from mean ; ; INPUT: ; ; data simple data array ; ; KEYWORDS: ; FILLVAL the fill value to be used to replace outlying data. ; ; CALLING SEQUENCE: ; ; data = clean_data(data,keywords...) ; function clean_data, data, FILLVAL=FILLVAL if not keyword_set(FILLVAL) then FILLVAL=1.0+e31; w=where(data ne FILLVAL,wn) if(wn eq 0) then begin print, "ERROR = No valid data found in function clean_data"; print, "STATUS = No valid data found. Re-select time interval."; endif ; mean= total(data[w[0:(wn-1)]])/fix(wn) ; RCJ 10/03/2003 The function moment needs data to have 2 or more elements. ; If that's not possible, then the mean will be the only valid element of ; data and the sdev will be 0. if n_elements(data[w[0:(wn-1)]]) gt 1 then begin result = moment(data[w[0:(wn-1)]],sdev=sig) mean=result[0] endif else begin mean=data[w[0:(wn-1)]] sig=0. endelse sig3=3.0*sig w=where(abs(data-mean) gt sig3, wn); ;TJK 4/8/2005 - add the next two lines because we have a case where ; all of the data values are exactly the same, and the "moment" routine ; above returns a sig value greater that the difference between the mean ; and data, so all values are set to fill, which isn't correct at all... ; So to make up for this apparent bug in the moment routine, do the following: t = where(data eq data[0], tn) if (tn eq n_elements(data)) then begin wn = 0 print, 'DEBUG clean_data - overriding results from moment func. because ' print, 'all data are the same valid value = ',data[0] endif if(wn gt 0) then data[w] = FILLVAL return, data end ;+ ; NAME: Function CONV_POS ; ; PURPOSE: Find virtual variables and compute their data w/ the component0, ; component1,... data. This function specifically converts position ; information from 1 coordinate system into another. ; ; INPUT: ; ; buf an IDL structure ; org_names an array of original variables sent to spd_cdawlib_read_mycdf ; ; KEYWORDS: ; COORD string corresponding to coordinate transformation ; default(SYN-GCI) ; (ANG-GSE) ; TSTART start time for synthetic data ; TSTOP start time for synthetic data ; ; CALLING SEQUENCE: ; ; newbuf = conv_pos(buf,org_names,keywords...) ; function conv_pos, buf, org_names, COORD=COORD, TSTART=TSTART, $ TSTOP=TSTOP, DEBUG=DEBUG, INDEX=INDEX status=0 ; Establish error handler catch, error_status if(error_status ne 0) then begin print, "ERROR= number: ",error_status," in conv_pos.pro" print, "ERROR= Message: ",!ERR_STRING status = -1 return, status endif org_names=strupcase(org_names) if keyword_set(DEBUG) then DEBUG=1L else DEBUG=0L if not keyword_set(INDEX) then INDEX=0L; if not keyword_set(COORD) then COORD="SYN-GCI"; if (keyword_set(TSTART) and keyword_set(TSTOP))then begin start_time = 0.0D0 ; initialize b = size(TSTART) & c = n_elements(b) if (b(c-2) eq 5) then start_time = TSTART $ ; double float already else if (b(c-2) eq 7) then start_time = encode_cdfepoch(TSTART); string stop_time = 0.0D0 ; initialize b = size(TSTOP) & c = n_elements(b) if (b(c-2) eq 5) then stop_time = TSTOP $ ; double float already else if (b(c-2) eq 7) then stop_time = encode_cdfepoch(TSTOP); string endif ;m3int=fix((stop_time - start_time)/(180.0*1000.0)) ; RCJ 07/10/02 Replaced fix w/ round. Fix won't work correctly on long integers m3int=round((stop_time - start_time)/(180.0*1000.0)) t3min=dblarr(m3int+1) failed=0 dep=parse_mydepend0(buf) depends=tag_names(dep) depend0=depends(dep.num) epoch1='Epoch1' namest=strupcase(tag_names(buf)) if((COORD eq "SYN-GCI") or (COORD eq "SYN-GEO")) then begin ; Determine time array depend0=strupcase(buf.(INDEX).depend_0) incep=where(namest eq depend0,w) incep=incep[0] names=tag_names(buf.(incep)) ntags=n_tags(buf.(incep)) ; Check to see if HANDLE a tag name wh=where(names eq 'HANDLE',whn) if(whn) then begin handle_value, buf.(incep).HANDLE,time datsz=size(time) endif else begin time=buf.(incep).dat endelse ; Determine position array ;help, buf.sc_pos_syngci, /struct vvtag_names=strarr(1) vvtag_indices = vv_names(buf,NAMES=vvtag_names) vvtag_names = strupcase(vvtag_names) ;TJK 12/15/2006, the following doesn't work when reading a ;a1_k0_mpa data file directly (w/o a master) because ;the data cdfs have one of the label variables incorrectly ;defined as a virtual variable, so you can't just assume ;the 1st one in vvtag_indices is the correct one. ; use the index passed in instead of vvtag_indices[0] ; cond0=buf.(vvtag_indices[0]).COMPONENT_0 cond0=buf.(index).COMPONENT_0 handle_value, buf.(cond0).HANDLE,data ;TJK 12/15/2006 these aren't right either - we'll use index ; fillval=buf.(vvtag_indices[0]).fillval ; rmin=buf.(vvtag_indices[0]).VALIDMIN[0] ; tmin=buf.(vvtag_indices[0]).VALIDMIN[1] ; pmin=buf.(vvtag_indices[0]).VALIDMIN[2] ; rmax=buf.(vvtag_indices[0]).VALIDMAX[0] ; tmax=buf.(vvtag_indices[0]).VALIDMAX[1] ; pmax=buf.(vvtag_indices[0]).VALIDMAX[2] fillval=buf.(index).fillval rmin=buf.(index).VALIDMIN[0] tmin=buf.(index).VALIDMIN[1] pmin=buf.(index).VALIDMIN[2] rmax=buf.(index).VALIDMAX[0] tmax=buf.(index).VALIDMAX[1] pmax=buf.(index).VALIDMAX[2] r=data[0,*] theta=data[1,*] phi=data[2,*] ; Check for radius in kilometers; switch to Re wrr=where(((r gt 36000.0) and (r lt 48000.0)),wrrn) if(wrrn gt 0) then r[wrr] = r[wrr]/6371.2 ; Check validity of data; if outside min and max set to fill rhi=where(r gt rmax,rhin) if(rhin gt 0) then r[rhi]=fillval rlo=where(r lt rmin,rlon) if(rlon gt 0) then r[rlo]=fillval ;print, rmax, rmin ;print, 'DEBUG',min(r, max=maxr) & print, maxr thi=where(theta gt tmax,thin) if(thin gt 0) then theta[thi]=fillval tlo=where(theta lt tmin,tlon) if(tlon gt 0) then theta[tlo]=fillval phii=where(phi gt pmax,phin) if(phin gt 0) then phi[phii]=fillval plo=where(phi lt pmin,plon) if(plon gt 0) then phi[plo]=fillval ; num=long(n_elements(time)) stime=time-time[0] dtime=(time[num-1] - time[0])/1000.0 d_m3time=dtime/(60.0*3.0) ; 3min/interval=(secs/interval) / (secs/3min) m3time=fix(d_m3time) ; Compute syn_phi, syn_r, and syn_theta syn_phi=dblarr(m3int+1) syn_theta=dblarr(m3int+1) syn_r=dblarr(m3int+1) newtime=dblarr(m3int+1) tst_theta=dblarr(num) ; Clean up any bad data; set to fill values outside 3-sigma phi=clean_data(phi,FILLVAL=fillval) theta=clean_data(theta,FILLVAL=fillval) r=clean_data(r,FILLVAL=fillval) wcp=where(phi ne fillval,wcnp) wct=where(theta ne fillval,wcnt) wcr=where(r ne fillval,wcnr) if((wcnp le 0) or (wcnt le 0) or (wcnr le 0)) then begin print, 'ERROR= Data all fill' print, 'STATUS= No valid data found for this time period' return, -1 endif if((wcnp eq 1) or (wcnt eq 1) or (wcnr eq 1)) then begin print, 'ERROR= Only one valid point' print, 'STATUS= Only one valid point found for this time period' return, -1 endif ; For short intervals < 10 points use wcnp otherwise average the 1st 10 points ; to obtain extrapolation parameters ;wcnp=wcnp-1 ;if(wcnp gt 10) then wcnp=10 else wcnp=wcnp-1 ; Compute average of all points mphi= total(phi[wcp[0:(wcnp-1)]])/fix(wcnp) mr= total(r(wcr[0:(wcnr-1)]))/fix(wcnr) mtheta= total(theta[wct[0:(wcnt-1)]])/fix(wcnt) ampl=double(max(theta[wct])) ;print, mphi, mr, mtheta, ampl wc=where(theta eq ampl,wcn) dphi=phi[wcp[wcnp-1]] - phi[wcp[0]] dr=r[wcr[wcnr-1]] - r[wcr[0]] dtheta=theta[wct[wcnt-1]] - theta[wct[0]] phi_rate=dphi/d_m3time r_rate=dr/d_m3time theta_rate=dtheta/d_m3time nominal_rate=0.75 new_rate= double(360.0/(nominal_rate + phi_rate)) ; print, nominal_rate, phi_rate, new_rate, r_rate ;!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ; Skip latitude daily variation approximation ;!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ; iter=0 ; sign=0 ; corr_coef=0.0 ; while(corr_coef lt 0.75) do begin ; T=time(wc[0])/180000.0 ;; T1=time(wc[0]-1)/180000.0 ;; T2=time(wc[0]-2)/180000.0 ;; T3=time(wc[0]+1)/180000.0 ;; T4=time(wc[0]+2)/180000.0 ; if(iter eq 0) then T=double(T) ;; if(iter eq 1) then T=double((T+T1)/2.0) ;; if(iter eq 2) then T=double((T1+T2)/2.0) ;; if(iter eq 3) then T=double((T+T3)/2.0) ;; if(iter eq 4) then T=double((T4+T3)/2.0) ;;print, ampl, T, mphi, mr, mtheta ; ;; determine array for correlation test ; for i=0L,num-1 do begin ; tm=time[i]/(180.0*1000.0) ;; tst_theta[i] = ampl*sin((2.0*(!pi))*(tm-T)/480.08898) ; if(sign eq 0) then tst_theta[i] = ampl*double(cos((2.0*(!pi))*(tm-T)/new_rate)) ; if(sign eq 1) then tst_theta[i] = ampl*double(sin((2.0*(!pi))*(tm-T)/new_rate)) ; endfor ; ; corr_coef=correlate(theta,tst_theta) ; if(DEBUG) then print, iter," CC = ", corr_coef ; ;; if(iter eq 4) then begin ; if(sign eq 0) then begin ; iter=0 ; sign = 1 ; endif ;; endif ; iter=iter+1 ;; if(iter gt 5) then goto, break ; if(iter gt 1) then goto, break ; endwhile ; break: ; ; if(corr_coef lt 0.75) then failed=1 ; failed=1 ; forces average theta variation to be used approx. 0.0 ; Generate 3-min data for i=0L,m3int do begin tm = (start_time)/180000.0 + i t3min[i]=i*180000.0 + start_time half=m3int/2 it=i-(half+1) syn_phi[i] = mphi + phi_rate*it ; syn_r[i] = mr + r_rate*i syn_r[i] = mr if(failed) then begin ; if(abs(mtheta) > 2.0) then begin ; print, 'WARNING: Check daily latitude variation.' ; return, -1; ; endif syn_theta[i] = 0.0 ; Can't compute daily variation; use this estimate ; syn_theta[i] = mtheta ; Can't compute daily variation; use this estimate ; syn_theta[i] = mtheta + theta_rate*i endif else begin ; syn_theta[i] = ampl*sin((2.0*(!pi))*(tm-T)/480.08898) if(sign eq 0) then syn_theta[i] = ampl*double(cos((2.0*(!pi))*(tm-T)/new_rate)) if(sign eq 1) then syn_theta[i] = ampl*double(sin((2.0*(!pi))*(tm-T)/new_rate)) endelse endfor ; print, t3min[0], syn_r[0], syn_theta[0], syn_phi[0] ; Convert spherical to cartesian ; Determine the offset of the given point from the origin. gei=dblarr(3,m3int+1) geo=dblarr(3,m3int+1) deg2rd=!pi/180.0 j=-1 for i=0L, m3int do begin CT = SIN(syn_theta[i]*deg2rd) ST = COS(syn_theta[i]*deg2rd) CP = COS(syn_phi[i]*deg2rd) SP = SIN(syn_phi[i]*deg2rd) ; Save syn-geo geo(0,i)=syn_r[i] geo(1,i)=syn_theta[i] geo(2,i)=syn_phi[i] ; Convert GEO spherical coordinates SGEO(1,2,3) [R,LAT,LON] ; to GEO cartesian coordinates in REs GEO(1,2,3) [X,Y,Z]. RHO = syn_r[i] * ST xgeo = RHO * CP ygeo = RHO * SP zgeo = syn_r[i] * CT xgei=0.0 & ygei=0.0 & zgei=0.0 ; Rotate 3-min vectors from geo to gci epoch=t3min[i] ; cdf_epoch, epoch, yr, mo, dy, hr, mn, sc, milli, /break ; if((i mod 100) eq 0) then print, epoch, yr, mo, dy, hr, mn, sc, milli geigeo,xgei,ygei,zgei,xgeo,ygeo,zgeo,j,epoch=epoch ; if((i mod 100) eq 0) then print, xgei,ygei,zgei,xgeo,ygeo,zgeo gei[0,i]=xgei gei[1,i]=ygei gei[2,i]=zgei endfor ; Modify existing structure nbuf=buf ; Modify depend0 (Epoch1), but don't add it again!! dc=where(depends eq 'EPOCH1',dcn) if(not dcn) then begin nu_ep_handle=handle_create(value=t3min) temp_buf=nbuf.(depend0) new=create_struct('EPOCH1',temp_buf) new.(epoch1).handle=nu_ep_handle new.(epoch1).VARNAME=epoch1 new.(epoch1).LABLAXIS=epoch1 endif ; Modify position data if(COORD eq "SYN-GCI") then begin nu_dat_handle=handle_create(value=gei) vin=where(vvtag_names eq 'SC_POS_SYNGCI',vinn) if(vinn) then begin nbuf.(vvtag_indices(vin[0])).handle=nu_dat_handle nbuf.(vvtag_indices(vin[0])).depend_0=epoch1 endif endif if(COORD eq "SYN-GEO") then begin nu_dat_handle=handle_create(value=geo) vin=where(vvtag_names eq 'SC_POS_SYNGEO',vinn) if(vinn) then begin nbuf.(vvtag_indices(vin[0])).handle=nu_dat_handle nbuf.(vvtag_indices(vin[0])).depend_0=epoch1 endif endif cond0=strupcase(cond0) pc=where(org_names eq cond0,pcn) ;blank=' ' if(pc[0] eq -1) then begin ; RCJ 06/16/2004 Only make epoch.var_type = metadata if no other ; variable needs epoch as its depend_0. in this case epoch ; should still be support_data. q=where(strlowcase(depends) eq 'epoch') if q[0] eq -1 then nbuf.epoch.var_type='metadata' ; RCJ 01/23/2007 The line below does not help listing. Does it do anything useful? ;nbuf.sc_pos_geo.depend_0=blank endif if(not dcn) then nbuf=create_struct(nbuf,new) endif if(COORD eq "ANG-GSE") then begin nbuf=buf vvtag_names=strarr(1) vvtag_indices = vv_names(buf,NAMES=vvtag_names) ; Determine time array ; depend0=depends(INDEX) ; incep=where(vvtag_names eq namest(INDEX),w) ; incep=incep[0] ;depend0=buf.(vvtag_indices(incep)).DEPEND_0 depend0=buf.(INDEX).DEPEND_0 ;print, depend0, INDEX incep=spd_cdawlib_tagindex(depend0, namest) incep=incep[0] names=tag_names(buf.(incep)) ntags=n_tags(buf.(incep)) ; Check to see if HANDLE a tag name wh=where(names eq 'HANDLE',whn) if(whn) then begin handle_value, buf.(incep).HANDLE,time datsz=size(time) endif else begin time=buf.(incep).dat endelse ; Determine position array ; indat=where(vvtag_names eq namest(INDEX),w) ; indat = indat[0] cond0=buf.(INDEX).COMPONENT_0 ;cond0=buf.(vvtag_indices(indat)).COMPONENT_0 ;print, cond0, INDEX handle_value, buf.(cond0).HANDLE,data ; Convert BGSE vector to angular BGSE; data_sz=size(data) ang_gse=dblarr(data_sz[1],data_sz[2]) ; cart_polar,data[0,*],data[1,*],data[2,*],ang_gse[0,*],ang_gse[1,*],$ ; ang_gse[2,*],1,/degrees ; ang_gse[0,*]=sqrt(data[0,*]*data[0,*]+data[1,*]*data[1,*]+data[2,*]*data[2,*]) ang_gse[0,*]=sqrt(data[0,*]^2+data[1,*]^2+data[2,*]^2) ang_gse[1,*]=90.0-(!radeg*acos(data[2,*]/ang_gse[0,*])) ang_gse[2,*]=!radeg*atan(data[1,*],data[0,*]) wc=where(ang_gse[2,*] lt 0.0,wcn) if(wcn gt 0) then ang_gse[2,wc] = ang_gse[2,wc]+360.0 nu_dat_handle=handle_create(value=ang_gse) ;nbuf.(vvtag_indices(indat)).handle=nu_dat_handle nbuf.(INDEX).handle=nu_dat_handle endif ; Check that all variables in the original variable list are declared as ; data otherwise set to metadata ; Find variables w/ var_type == data status = check_myvartype(nbuf, org_names) return, nbuf end ;to get help: IDL> ptg,/help ; ancillary routines -------------------------------------------- FUNCTION dtand,x RETURN,DOUBLE(TAN(x*!DTOR)) END FUNCTION datand,x RETURN,DOUBLE(ATAN(x)/!DTOR) END FUNCTION fgeodeP,a,b,v1x,v1y,v1z,v2x,v2y,v2z RETURN,v1x*v2x + v1y*v2y + v1z*v2z * a*a/(b*b) END ;--------------------------------------------------------------- PRO vector_to_ra_decP,x,y,z,ra,dec fill_value = -1.D31 ndx = WHERE(z NE 0,count) IF(count GT 0) THEN dec[ndx] = 90.*z[ndx]/ABS(z[ndx]) tmp = SQRT(x*x + y*y) ndx = WHERE(tmp NE 0,count) IF (count GT 0) THEN BEGIN dec[ndx] = atan2d(z[ndx],tmp[ndx]) ra[ndx] = atan2d(y[ndx],x[ndx]) ENDIF ndx = WHERE((ra LT 0) AND (ra NE fill_value),count) IF (count GT 0) THEN ra[ndx] = ra[ndx] + 360. END ;--------------------------------------------------------------- PRO drtollP,x,y,z,lat,lon,r ; RTB gci point validity check if((abs(x) gt 10000.0) or (abs(y) gt 10000.0) or (abs(z) gt 10000.0)) $ then begin lat = -1.0e+31 lon = -1.0e+31 r = -1.0e+31 endif else begin lat = atan2d(z,SQRT(x*x + y*y)) lon = atan2d(y,x) r = SQRT(x*x + y*y + z*z) endelse ; RTB comment ; tmp = WHERE(x EQ Y) AND WHERE(x EQ 0) ; IF ((size(tmp))[0] NE 0) THEN BEGIN ; lat(tmp) = DOUBLE(90.D * z(tmp)/ABS(z(tmp))) ; lon(tmp) = 0.D ; r = 6371.D ; ENDIF tmp2 = WHERE(lon LT 0) IF ((size(tmp2))[0] NE 0) THEN BEGIN lon(tmp2) = lon(tmp2) + 360.D ENDIF ; RTB added 4/98 avoid boundary tmp3 = where(lon eq 0.0) if(tmp3[0] ne -1) then lon(tmp3) = 0.01D tmp4 = where(lon eq 360.0) if(tmp4[0] ne -1) then lon(tmp4) = 359.09D END ;--------------------------------------------------------------- PRO get_scalarP,Ox,Oy,Oz,Lx,Ly,Lz,emis_hgt,ncols,nrows,s,f ;... Equatoral radius (km) and polar flattening of the earth ; Ref: Table 15.4, 'Explanatory Supplement to the ; Astronomical Almanac,' K. Seidelmann, ed. (1992). re_eq = 6378.136D inv_f = 298.257D ;... initialize output s = DBLARR(ncols,nrows) s1 = DBLARR(ncols,nrows) s2 = DBLARR(ncols,nrows) ;... get polar radius re_po = re_eq*(1.D - 1.D /inv_f) ;... get radii to assumed emission height ree = re_eq + emis_hgt rep = re_po + emis_hgt ;... get flattening factor based on new radii f = (ree - rep)/ree ;... get elements of quadratic formula a = fgeodeP(ree,rep,Lx,Ly,Lz,Lx,Ly,Lz) b = fgeodeP(ree,rep,Lx,Ly,Lz,Ox,Oy,Oz) * 2.D c = fgeodeP(ree,rep,Ox,Oy,Oz,Ox,Oy,Oz) - ree*ree ;... check solutions to quadratic formula determinant = b*b - 4.D * a*c ;... remove points off the earth determinant = determinant > 0. tmp_d2 = WHERE(determinant EQ 0.,count) IF(count GT 0) THEN b[tmp_d2] = 0.D ;... solve quadratic formula (choose smallest solution) s1 = ( -b + SQRT(determinant) ) / ( 2.D *a ) s2 = ( -b - SQRT(determinant) ) / ( 2.D *a ) s = s1') new_display_type='' ; Count the number of '=' to determine the number of instructions b=0 ;for i=0,strlen(a[1])-1 do if (strmid(a[1],i,1) eq '=') then b=b+1 for j=0,n_elements(a)-1 do begin if strpos(a[j],'=') ne -1 then begin for i=0,strlen(a[j])-1 do if (strmid(a[j],i,1) eq '=') then b=b+1 eq_index=j ; element of display_type for which '=' exists endif else begin new_display_type=[new_display_type,a[j]] ; make array; add '>' later endelse endfor if (b ge 1) then begin ilist = strarr(b) endif else begin ;no y=var(*,1) instructions found, return the parents data astruct.(index).handle = astruct.(var_idx).handle return, astruct endelse ;if instructions are found, continue on ;looking for syntax like stack_plot>y=FLUX_SEL_ENERGY_STACK(*,1) ; Dissect the input string into its separate instructions inum = 0 & next_target=',' ; initialize for i=0,strlen(a[eq_index])-1 do begin c = strmid(a[eq_index],i,1) ; get next character in string if (c eq next_target) then begin if (next_target eq ',') then inum = inum + 1 if (next_target eq ')') then begin ilist[inum] = ilist[inum] + c & next_target = ',' endif endif else begin ilist[inum] = ilist[inum] + c ; copy to instruction list if (c eq '(') then next_target = ')' endelse endfor ;we don't need this loop for y=var(*,n) or y=var(n,*) or y=var(n,n,*) ;but we do need the loop for y=var(1,1),y=var(1,5), etc. ;help, ilist ;stop; num_lists = n_elements(ilist) for inum=0,num_lists-1 do begin b=strpos(ilist[inum],'y=') & c=strpos(ilist[inum],'Y=') if c gt b then b=c if (b ne -1) then begin ; extract the name of the y variable and elist c = spd_cdawlib_break_mystring(ilist[inum],delimiter='(') if (n_elements(c) eq 2) then rem = strmid(c[1], 0,strlen(c[1])-1) if (rem ne '') then begin ;apply the reduction syntax to the parent array new_array = parent_array[rem,*];last dim. is records ;stop; if (num_lists eq 1) then begin new_array = reform(new_array) ;remove 1-d dimensions endif else begin temp_array = append_mydata(new_array, temp_array) if (inum eq num_lists-1) then new_array = reform(temp_array) ;print, 'check this syntax ' ;stop; endelse ; print, 'New reduced array ' & help, new_array endif endif endfor endif else print, 'make_stack_array - DISPLAY_TYPE needed' endif else print, 'make_stack_array - parent variable not found' ;Put the reduced sized array in the virtual variables handle temp = handle_create(value=new_array) astruct.(index).HANDLE = temp ;astruct.(index).DISPLAY_TYPE = a[0] ; should be just stack_plot ndt='' ; start at 1 because 1st element of new_display_type is '' for i=1,n_elements(new_display_type)-2 do ndt=ndt+strtrim(new_display_type[i],2)+'>' ; last element: ndt=ndt+strtrim(new_display_type[i]) astruct.(index).DISPLAY_TYPE = ndt ; should be just stack_plot ; Check that all variables in the original variable list are declared ; as data otherwise set to support_data status = check_myvartype(astruct, org_names) return, astruct end pro spd_cdawlib_virtual_funcs end