This page was created by the IDL library routine mk_html_help2.

Last modified: Thu Aug 6 12:53:14 2020.


Directory Listing of Routines


Routine Descriptions

EXPAND_TILDE()

[Next Routine] [List of Routines]
 NAME:
      EXPAND_TILDE()
               
 PURPOSE: 
       Expand tilde in UNIX directory names
               
 CALLING SEQUENCE: 
       IDL> output=expand_tilde(input)
    
 INPUTS: 
       INPUT = input file or directory name, scalar string

 OUTPUT:
       Returns expanded filename, scalar string
               
 EXAMPLES: 
       output=expand_tilde('~zarro/test.doc')
               ---> output='/usr/users/zarro'

 NOTES:
       This version of EXPAND_TILDE differs from the version in the Solar
       Library in that it does not call the functions EXIST and IDL_RELEASE.
       However, it should work identically.
 PROCEDURE CALLS:
       None.
 REVISION HISTORY: 
       Version 1,  17-Feb-1997,  D M Zarro.  Written
       Transfered from Solar Library   W. Landsman   Sep. 1997
       Made more robust  D. Zarro/W. Landsman  Sep. 2000
       Made even more robust (since things like ~zarro weren't being expanded)
       Zarro (EITI/GSFC, Mar 2001)

(See general/missions/rbsp/efw/utils/expand_tilde.pro)


FINDPATH[2]

[Previous Routine] [Next Routine] [List of Routines]
FUNCTION: findpath.pro

PURPOSE: Finds the path to a particular file in current IDL paths

ARGUMENTS:
    FILENAME  -> Name of the file to find   - STRING
    PATH      <- Path to file (without "/") - STRING

RETURNS:  Status of find
            0 - Failure
            1 - Success (exact match)
            2 - Success (after adding ".pro")

KEYWORDS:
    EXACT    /  Find exact match only (Don't try to add '.pro')
    VERBOSE  /  Print out search pathes

CALLING SEQUENCE: found=findpath('filename',pathname)
                  case found of
                    0 : ERROR
                    1 : fullpath=pathname+'/'+filename
                    2 : fullpath=pathname+'/'+filename+'.pro'
                  endcase
              or
                  if not findpath('filename',path,/exact) then ERROR

NOTES:  By default, FINDPATH searches for exact match.  If not found
        looks for 'filename' with ".pro" appended (unless /EXACT keyword
        is set).

CREATED BY: John P. Dombeck 7/03/2001

MODIFICATION HISTORY:

  07/03/01- J. Dombeck    Original writing
  06/25/04- J. Dombeck    Added VERBOSE keyword
                          Changed close -> free_lun

(See general/missions/rbsp/efw/utils/findpath.pro)


JBT_DATE2JDAY (FUNCTION)

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
   jbt_date2jday (function)

 PURPOSE:
   Convert a date string in format 'yyyy-mm-dd', such as '2012-10-16', into a
   longword integer Julian day number.

 CATEGORIES:
   Utilities

 CALLING SEQUENCE:
   result = jbt_date2jday(date)

 ARGUMENTS:
   date: (In, required) A date string in format 'yyyy-mm-dd', such as
         '2012-10-16'.

 KEYWORDS:

 COMMON BLOCKS:

 EXAMPLES:

 SEE ALSO:

 HISTORY:
   2012-11-02: Created by Jianbao Tao (JBT), SSL, UC Berkley.
   2012-11-02: Initial release to TDAS. JBT, SSL/UCB.

 VERSION:
 $LastChangedBy: jianbao_tao $
 $LastChangedDate: 2012-11-02 16:35:10 -0700 (Fri, 02 Nov 2012) $
 $LastChangedRevision: 11172 $
 $URL: svn+ssh://thmsvn@ambrosia.ssl.berkeley.edu/repos/spdsoft/tags/spedas_4_0/general/missions/rbsp/efw/utils/jbt_date2jday.pro $

(See general/missions/rbsp/efw/utils/jbt_date2jday.pro)


JBT_EXTREMA (FUNCTION)

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
   jbt_extrema (function)

 PURPOSE:
   Find extrema in a numerical array and return their indices.

 CATEGORIES:

 CALLING SEQUENCE:
   result = jbt_extrema(array, interp_nan = interp_nan, min_only = min_only, $
     max_only = max_only, threshold = threshold)

 ARGUMENTS:
   array: (In, required) The array to find extrema in.

 KEYWORDS:
   /interp_nan: If set, remove NaNs by linear interpolation before searching
         for extrema.
   /min_only: If set, only return minima.
   /max_only: If set, only return maxima.
   threshold: (In, optional) Threshold for changing sense. For example, if
         threshold is 10 and A[i] and A[i+1] are two adjacent points in a local
         segment that generally has positive slope, then the segment will be
         treated as a full positive-slope segment if A[i+1]-A[i] > -10.
         Default = 0.

 COMMON BLOCKS:

 EXAMPLES:
     ; IDL code example
     npt = 100
     a = randomn(seed, npt)
     x = findgen(npt)
     ind = jbt_extrema(a)
     plot, x, a
     oplot, x[ind], a[ind], psym = 2, color = 6

 SEE ALSO:

 HISTORY:
   2012-11-10: Created by Jianbao Tao (JBT), SSL, UC Berkley.
   2012-11-12: Initial release in TDAS. JBT, SSL/UCB.

 VERSION:
 $LastChangedBy: jianbao_tao $
 $LastChangedDate: 2012-11-12 08:36:20 -0800 (Mon, 12 Nov 2012) $
 $LastChangedRevision: 11219 $
 $URL: svn+ssh://thmsvn@ambrosia.ssl.berkeley.edu/repos/spdsoft/tags/spedas_4_0/general/missions/rbsp/efw/utils/jbt_extrema.pro $

(See general/missions/rbsp/efw/utils/jbt_extrema.pro)


JBT_FEXIST (FUNCTION)

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
   jbt_fexist (function)

 CATEGORY:

 PURPOSE:
   Check the existence of a local file. Return 1 if the file exists, or 0 if
   not.

 CALLING SEQUENCE:
   result = jbt_fexist(file)

 ARGUMENTS:
   file: (In, required) A string of a local file to be checked.

 KEYWORDS:

 EXAMPLES:

 SEE ALSO:

 HISTORY:
   2011-05-01: Created by Jianbao Tao (JBT), CU/LASP.
   2012-11-02: Initial release to TDAS. JBT, SSL/UCB.

 VERSION:
 $LastChangedBy: jianbao_tao $
 $LastChangedDate: 2012-11-02 16:35:10 -0700 (Fri, 02 Nov 2012) $
 $LastChangedRevision: 11172 $
 $URL: svn+ssh://thmsvn@ambrosia.ssl.berkeley.edu/repos/spdsoft/tags/spedas_4_0/general/missions/rbsp/efw/utils/jbt_fexist.pro $

(See general/missions/rbsp/efw/utils/jbt_fexist.pro)


JBT_FILE_LATEST (FUNCTION)

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
   jbt_file_latest (function)

 PURPOSE:
   Return the path of the latest file within a folder.

 CATEGORIES:

 CALLING SEQUENCE:
   result = jbt_file_latest(dir)

 ARGUMENTS:
   dir: (In, required) A string of a local directory.

 KEYWORDS:

 COMMON BLOCKS:

 EXAMPLES:

 SEE ALSO:

 HISTORY:
   2012-10-28: Created by Jianbao Tao (JBT), SSL, UC Berkley.
   2012-11-02: Initial release to TDAS. JBT, SSL/UCB.


 VERSION:
 $LastChangedBy: jianbao_tao $
 $LastChangedDate: 2012-11-02 16:35:10 -0700 (Fri, 02 Nov 2012) $
 $LastChangedRevision: 11172 $
 $URL: svn+ssh://thmsvn@ambrosia.ssl.berkeley.edu/repos/spdsoft/tags/spedas_4_0/general/missions/rbsp/efw/utils/jbt_file_latest.pro $

(See general/missions/rbsp/efw/utils/jbt_file_latest.pro)


JBT_GET_LINES (FUNCTION)

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
   jbt_get_lines (function)

 PURPOSE:
   Get all lines of a text file.

 CATEGORY:

 CALLING SEQUENCE:
   result = jbt_get_lines(file)

 ARGUMENTS:
   file: (In, required) A string of a local text file to load.

 KEYWORDS:

 COMMON BLOCKS:

 SIDE EFFECTS:

 RESTRICTIONS:

 EXAMPLE:

 SEE ALSO:

 MODIFICATION HISTORY:
   2011-05-27: Created by Jianbao Tao, CU/LASP.
   2012-11-02: Initial release to TDAS. JBT, SSL/UCB.

(See general/missions/rbsp/efw/utils/jbt_get_lines.pro)


JBT_ICONSEC (FUNCTION)

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
   jbt_iconsec (function)

 CATEGORY:

 PURPOSE:
   Given an array of indices, find consecutive sections in the array, and
   return the starting and ending indices of each section. The returned value
   has dimension [nsec, 2]

 CALLING SEQUENCE:
   result = jbt_iconsec(indarr, nsec = nsec, npt = npt)

 ARGUMENTS:
   indarr: (In, required) An index array.

 KEYWORDS:
   nsec: (Out, optional) Number of consective sections in indarr.
   npt: (Out, optional) Number of points in each section.

 EXAMPLES:

 SEE ALSO:

 HISTORY:
   2011-05-20: Created by Jianbao Tao (JBT), CU/LASP.
   2012-11-12: Initial release in TDAS. JBT, SSL/UCB.

 VERSION:
 $LastChangedBy: jianbao_tao $
 $LastChangedDate: 2012-11-12 08:36:20 -0800 (Mon, 12 Nov 2012) $
 $LastChangedRevision: 11219 $
 $URL: svn+ssh://thmsvn@ambrosia.ssl.berkeley.edu/repos/spdsoft/tags/spedas_4_0/general/missions/rbsp/efw/utils/jbt_iconsec.pro $

(See general/missions/rbsp/efw/utils/jbt_iconsec.pro)


JBT_JDAY2DATE (FUNCTION)

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
   jbt_jday2date (function)

 PURPOSE:
   Convert a longword integer Julian day number into a date string in format
   'yyyy-mm-dd', such as '2012-10-16'.

 CATEGORIES:

 CALLING SEQUENCE:
   result = jbt_jday2date(jday)

 ARGUMENTS:
   jday: (In, required) A longword integer Julian day number.

 KEYWORDS:

 COMMON BLOCKS:

 EXAMPLES:

 SEE ALSO:

 HISTORY:
   2012-11-02: Created by Jianbao Tao (JBT), SSL, UC Berkley.
   2012-11-02: Initial release to TDAS.


 VERSION:
 $LastChangedBy: jianbao_tao $
 $LastChangedDate: 2012-11-02 16:35:10 -0700 (Fri, 02 Nov 2012) $
 $LastChangedRevision: 11172 $
 $URL: svn+ssh://thmsvn@ambrosia.ssl.berkeley.edu/repos/spdsoft/tags/spedas_4_0/general/missions/rbsp/efw/utils/jbt_jday2date.pro $

(See general/missions/rbsp/efw/utils/jbt_jday2date.pro)


JBT_TPLOT_POS (FUNCTION)

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
   jbt_tplot_pos (function)

 PURPOSE:
   Get the positions of tplot panels. The returned array has the form 
   [n_panels, 4]. The meanings of the 4 values of each panel are:
       [*, 0]: left x
       [*, 1]: bottom y
       [*, 2]: right x
       [*, 3]: top y

 CATEGORIES:

 CALLING SEQUENCE:
   pos = jbt_tplot_pos(npanels = npanels, xpos = xpos, ypos = ypos, $
   enclose = enclose)
   
   xpos and ypos store locations for plots. For example, 
       plots, xpos[0,*], ypos[0,*], color = 6 ; 6 = red
   will draw lines along the top panel frame.

 ARGUMENTS:

 KEYWORDS:
     npanels: (Output, optional)
     xpos: (Output, optional)
     ypos: (Output, optional)
     /enclose: (Input, optional)

 COMMON BLOCKS:

 EXAMPLES:

 SEE ALSO:

 HISTORY:
   2012-08-24: Created by Jianbao Tao(JBT), SSL, UC Berkeley.

 VERSION:
 $LastChangedBy: jianbao_tao $
 $LastChangedDate: 2012-11-02 16:35:10 -0700 (Fri, 02 Nov 2012) $
 $LastChangedRevision: 11172 $
 $URL: svn+ssh://thmsvn@ambrosia.ssl.berkeley.edu/repos/spdsoft/tags/spedas_4_0/general/missions/rbsp/efw/utils/jbt_tplot_pos.pro $

(See general/missions/rbsp/efw/utils/jbt_tplot_pos.pro)


RBSP_BTRANGE (PROCEDURE)

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
   rbsp_btrange (procedure)

 PURPOSE:
     This routine is to find the starting time and ending time of each
     continuous segment (burst, usually) of a give tplot variable which
     essentially is specified by a tplot name such as 'rbspa_efw_eb2'.

 CATEGORIES:

 CALLING SEQUENCE:
   rbsp_btrange, tvar, btrange = btrange, nbursts = nbursts, tind = tind, $
                   tlen = tlen, structure = structure

 ARGUMENTS:
   tvar: (INPUT, REQUIRED). The name of a tplot variable. If keyword STRUCTURE
         is set, tvar should be a tplot data structure from get_data.

 KEYWORDS:
    btrange: (OUTPUT, OPTIONAL) A named variable to return a 2D array as
             [number_of_total_bursts, 2] which stores the the starting time and
             the ending time of each continuous burst.
    nbursts: (OUTPUT, OPTIONAL) A named variable to return the number of
           bursts.
    tind: (OUTPUT, OPTIONAL) A named variable to return a 2D array of the index
           of starting and ending time points with structure
           [[starting],[ending]]
    tlen: (OUTPUT, OPTIONAL) A named variable to return the time lengths of
          all bursts.
    /structure: If set, tvar should be a tplot data structure.

 COMMON BLOCKS:

 EXAMPLES:

 SEE ALSO:

 HISTORY:
   2012-08-23: Created by Jianbao Tao (JBT), SSL, UC Berkley.

(See general/missions/rbsp/efw/utils/rbsp_btrange.pro)


RBSP_DECIMATE (PROCEDURE)

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
   rbsp_decimate (procedure)

 PURPOSE:
   Decimate a tplot variable. Be default, the routine only decimate the input
   data by one level, i.e., sample rate reduced by half.

 CATEGORIES:

 CALLING SEQUENCE:
   rbsp_decimate, tvar, upper = upper, level = level, newname = newname

 ARGUMENTS:
   tvar: (In, required) Tplot variable to be decimated.

 KEYWORDS:
   upper: (In, optional) If set, the output data's sample rate is no higher
         than the value of upper.
   level: (In, optional) Decimation level. Default = 1.
   newname: (In, optional) A tplot name for the output data. Default = tvar.

 COMMON BLOCKS:

 EXAMPLES:

 SEE ALSO:

 HISTORY:
   2012-11-03: Created by Jianbao Tao (JBT), SSL, UC Berkley.
   2012-11-05: Initial release to TDAS. JBT, SSL/UCB.


 VERSION:
 $LastChangedBy: aaronbreneman $
 $LastChangedDate: 2015-09-28 13:02:01 -0700 (Mon, 28 Sep 2015) $
 $LastChangedRevision: 18950 $
 $URL: svn+ssh://thmsvn@ambrosia.ssl.berkeley.edu/repos/spdsoft/tags/spedas_4_0/general/missions/rbsp/efw/utils/rbsp_decimate.pro $

(See general/missions/rbsp/efw/utils/rbsp_decimate.pro)


RBSP_MIN_VAR

[Previous Routine] [Next Routine] [List of Routines]
FUNCTION: rbsp_min_var.pro

PURPOSE: Minimum Variance Analysis

ARGUMENTS: 
    X_DATA   -> X component of original data
    Y_DATA   -> Y component of original data
    Z_DATA   -> Z component of original data


RETURNS: Minimum variance rotation matix (Eigen vectors, min to max)
           0 on failure

         The returned matrix is in the rotation matrix form where
                N = R * O
           where
               N = New matrix (Rotated into Min. Var. Coordinates)
               R = Rotation matrix (Result from MIN_VAR)
               O = Original matrix
               * = Standard Matrix Multipication

KEYWORDS:
    EIG_VALS <- Eigen values of minimum variance analysis (min to max)


CALLING SEQUENCE: 
       vectors=min_var(data.x,data.y,data.z,eig_vals=values)
                 or
       rot_arr=min_var(orig_arr[*,0],orig_arr[*,1],orig_arr[*,2]) ## orig_arr
                 or
       rot_arr=orig_arr # min_var(orig_arr[*,0],orig_arr[*,1],orig_arr[*,2])
                 or
       rot_arr=orig_arr ##
                 transpose(min_var(orig_arr[0,*],orig_arr[1,*],orig_arr[2,*]))
        (These last three forms will crash if min_var fails)


NOTES: 

CREATED BY: John Dombeck August 2001

MODIFICATION HISTORY: 
	08/06/01-J. Dombeck              Created
	08/11/11-A. Paradise		 Added NAN handling, warning if NaN values exist
	02/26/2014  Aaron Breneman   changed name to rbsp_min_var.pro. This version is exactly
								the same as original except for name change.
INCLUDED MODULES:
   min_var

LIBRARIES USED:
   None

DEPENDANCIES
   None


 VERSION: 
   $LastChangedBy: aaronbreneman $
   $LastChangedDate: 2014-02-26 13:46:35 -0800 (Wed, 26 Feb 2014) $
   $LastChangedRevision: 14448 $
   $URL: svn+ssh://thmsvn@ambrosia.ssl.berkeley.edu/repos/spdsoft/tags/spedas_4_0/general/missions/rbsp/efw/utils/rbsp_min_var.pro $

(See general/missions/rbsp/efw/utils/rbsp_min_var.pro)


RBSP_MIN_VAR_ROT

[Previous Routine] [Next Routine] [List of Routines]
*****************************************************************************************

  FUNCTION :  rbsp_min_var_rot.pro
  PURPOSE  :  Calculates the minimum variance matrix of some vector array of a 
               particular input field along with uncertainties and angular 
               rotation from original coordinate system.

==-----------------------------------------------------------------------------
*******************************************************************************
 Error Analysis from: A.V. Khrabrov and B.U.O. Sonnerup, JGR Vol. 103, 1998.


avsra = WHERE(tsall LE timesta+30.d0 AND tsall GE timesta-30.d0,avsa)
myrotma = MIN_VAR(myavgmax[avsra],myavgmay[avsra],myavgmaz[avsra],EIG_VALS=myeiga)

 dphi[i,j] = +/- SQRT(lam_3*(lam_[i]+lam_[j]-lam_3)/((K-1)*(lam_[i] - lam_[j])^2))

 dphi = angular standard deviation (radians) of vector x[i] toward/away from 
         vector x[j]
*******************************************************************************
  Hoppe et. al. [1981] :
      lam_3 : Max Variance
      lam_2 : Intermediate Variance
      lam_1 : MInimum Variance

        [Assume isotropic "noise" in signals]
      Variance due to signal (along MAX VARIANCE) : lam_1 - lam_3
      Variance due to signal (along INT VARIANCE) : lam_2 - lam_3

      Maximum Angular Change (along MIN VARIANCE) : th_min = ATAN(lam_3/(lam_2 - lam_3))
      Maximum Angular Change (along MAX VARIANCE) : th_max = ATAN(lam_3/(lam_1 - lam_2))

  -The direction of maximum variance in the plane of maximum variance is determined
    by the size of the difference between the two variances in this plane compared
    to noise.

  -EXAMPLES/ARGUMENTS
    IF lam_2 = lam_3   => th_min is NOT DEFINED AND th_max is NOT DEFINED
    IF lam_2 = 2*lam_3 => th_min = !PI/4
    IF lam_2 = 2*lam_3 => th_min = !PI/30

    IF lam_1 = lam_2 >> lam_3 => Minimum Variance Direction is still well defined!


*******************************************************************************
  Mazelle et. al. [2003] :
        Same Min. Var. variable definitions

       th_min = SQRT((lam_3*lam_2)/(N-1)/(lam_2 - lam_3)^2)
        {where : N = # of vectors measured, or # of data samples}
*******************************************************************************
==-----------------------------------------------------------------------------

  CALLS:  
               rbsp_min_var.pro

  INPUT:
               FIELD  :  some [n,3] or [3,n] array of vectors

  EXAMPLES:

  KEYWORDS:  
               RANGE      :  2-element array defining the start and end point elements
                               to use for calculating the min. var.
               NOMSSG     :  If set, TPLOT will NOT print out the index and TPLOT handle
                               of the variables being plotted
               BKG_FIELD  :  [3]-Element vector for the background field to dot with
                               MV-Vector produced in program
                               [Default = DC(smoothed) value of input FIELD]

   CHANGED:  1)  Changed calculation for angle of prop. w/ respect to B-field
                   to the method defined directly above     [09/29/2008   v1.0.2]
             2)  Corrected theta_{kB} calculation           [10/05/2008   v1.0.3]
             3)  Changed theta_{kB} calculation, added calculation of minimum variance
                   eigenvector error, and changed return structure 
                                                            [01/20/2009   v1.1.0]
             4)  Fixed theta_kB calc. (forgot to normalize B-field) 
                                                            [01/22/2009   v1.1.1]
             5)  Added keywords:  NOMSSG and BKG_FIELD      [12/04/2009   v1.2.0]
             4)  Fixed a typo in definition of GN variable  [12/08/2009   v1.2.1]

   CREATED:  06/29/2008
   CREATED BY:  Lynn B. Wilson III
    LAST MODIFIED:  12/08/2009   v1.2.1
    MODIFIED BY: Lynn B. Wilson III
				  Aaron Breneman - changed name to rbsp_min_var_rot.pro. This version
									is unchanged from original aside from name change

*****************************************************************************************
 VERSION: 
   $LastChangedBy: aaronbreneman $
   $LastChangedDate: 2016-09-02 10:42:46 -0700 (Fri, 02 Sep 2016) $
   $LastChangedRevision: 21790 $
   $URL: svn+ssh://thmsvn@ambrosia.ssl.berkeley.edu/repos/spdsoft/tags/spedas_4_0/general/missions/rbsp/efw/utils/rbsp_min_var_rot.pro $

(See general/missions/rbsp/efw/utils/rbsp_min_var_rot.pro)


RBSP_ROTATE_FIELD_2_VEC

[Previous Routine] [Next Routine] [List of Routines]
 NAME: rotate_field_2_vec.pro
 SYNTAX: rbsp_rotate_field_2_vec,'waveform','vec'
			where 'waveform' is a tplot variable and 'vec'
			is either a tplot variable or an array of [3]

 PURPOSE: Returns rotation matrix and the input waveform or vector rotated to one of the following systems.
				a) Min Var - input "vec" (e.g. DC Bfield) only
					z-hat defined to be direction of "vec"
					y_hat is given by vec cross x_max, where x_max is the maximum variance eigenvector
					x_hat - max variance eigenvector always lies in x-z plane
					Uses this system by default unless /efa is set or "vec2" is input
				b) Two vec - input "vec" and "vec2"
					z-hat is direction of "vec"
					y-hat = (vec x vec2)/|vec2 x vec|
					x-hat = (y-hat x vec)/|vec x y-hat|  (vec2 is in x-z plane)
					Uses this if "vec2" is set
         ***Can be used to define a radial, azimuthal, Bo coord system with
           vec = Bo
           vec2 = r  (radial direction)
         So,  z-hat ~ Bo
              y-hat ~ (Bo x r)        (azimuthal)
              x-hat ~ (y-hat x Bo)    (radial)

				c) EFA - similar to Two Vec, but doesn't require an additional input vector.
         Instead uses the input x-hat (i.e. [1,0,0])
					z-hat is direction of "vec"
         and x-z plane consists of Vec and [1,0,0]
					Uses this if /efa is set

 INPUT: Tplot variable names of:
       waveform -> Name of tplot variable of [m,3] or [3] waveform data. Note that if the
					Min var rotation is requested then must input a [m,3] where m>1
	vec   -> [3] element vector OR name of tplot variable
	         containing [n,3] element vector to represent the z-hat direction. Ex.
					Bo in the coord system of "waveform".
					Note that the coordinates of
					"vec" and "waveform" must be
					the same!
                                       Also note that m != n necessarily



(See general/missions/rbsp/efw/utils/rbsp_rotate_field_2_vec.pro)


RBSP_SAMPLE_RATE

[Previous Routine] [Next Routine] [List of Routines]
 NAME: rbsp_sample_rate.pro
 SYNTAX: 
 PURPOSE: Determines the sample rate of an input time series of data with the
                 ability to set gap thresholds to avoid including them in the
                 calculation.
 INPUT: time :  [N]-element array of time series times
 OUTPUT: 
 KEYWORDS: 
               GAP_THRESH   :  Scalar defining the maximum data gap [s] allowed in
                                 the calculation
                                 [Default = MAX(TIME) - MIN(TIME)]
               AVERAGE      :  If set, routine returns the scalar average sample rate
                                 [Default = 0, which returns an array of sample rates]
               OUT_MED_AVG  :  Set to a named variable to return the median and average
                                 values of the sample rate if the user wants all values
                                 as well
 HISTORY:  ;   CREATED:  03/28/2012  Lynn B. Wilson III
    
 NOTES:          
               1)  The output is the sample rate in [# samples per unit time]
               2)  If GAP_THRESH is set too small, then the returned result is a 

 VERSION: 
   $LastChangedBy: aaronbreneman $
   $LastChangedDate: 2014-10-15 12:38:05 -0700 (Wed, 15 Oct 2014) $
   $LastChangedRevision: 15997 $
   $URL: svn+ssh://thmsvn@ambrosia.ssl.berkeley.edu/repos/spdsoft/tags/spedas_4_0/general/missions/rbsp/efw/utils/rbsp_sample_rate.pro $

(See general/missions/rbsp/efw/utils/rbsp_sample_rate.pro)


TPLOT_ZOOM (PROCEDURE)

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
   tplot_zoom (procedure)

 PURPOSE:
   This is basically a wrapper of some of the functions of tlimit and timebar.

 CATEGORY:
   Widget

 CALLING SEQUENCE:
   tplot_zoom, reset = reset, horizontal = horizontal

   Use following calls to change the styles of time bars and y-bars (horizontal
   bars).
   
     tplot_zoom_set_ybar, linestyle = linestyle, color = color, $
       thick = thick, reset = reset
     tplot_zoom_set_tbar, linestyle = linestyle, color = color, $
       thick = thick, reset = reset

 KEYWORDS:
   /reset: In, optional
         If set, the common block tplot_zoom_com will be reset.
   /horizontal: In, optional
         If set, the shape of the widget will be a horizontal bar.

 INPUTS:   
   None.

 SEE ALSO:
   tplot, tlimit, ctime, timebar

 MODIFICATION HISTORY:
   2011-09-06: Created by Jianbao Tao (JBT) at CU/LASP for REE, JBT's PhD
               advisor, to demo tplot capabilities in a MMS meeting.
   2012-06-15: JBT, CU/LASP. 
         1. Updated the documentation header.
         2. Cleaned the code.
   2012-06-26: JBT, CU/LASP. (Obsolete comment. JBT, 2012-10-31)
         1. Added more comments.
         2. Replaced 'Zoom In', 'Zoom Out', 'Pan Forward', and 'Pan Backward'
            buttons with ' + + ', '  +  ', '  -  ', ' - - ', ' < < ', '  <  ',
            '  >  ', and ' > > ' buttons.
         3. Added the 'Full Time Span' and 'Add Time Bar(s)' buttons.
   2012-10-31: JBT, SSL/UCB. Initial release in TDAS.
   2013-06-20: JBT. Fixed a bug when tplot options do not include the window
               option.

 VERSION:
 $LastChangedBy: jianbao_tao $
 $LastChangedDate: 2013-06-20 08:46:53 -0700 (Thu, 20 Jun 2013) $
 $LastChangedRevision: 12558 $
 $URL: svn+ssh://thmsvn@ambrosia.ssl.berkeley.edu/repos/spdsoft/tags/spedas_4_0/general/missions/rbsp/efw/utils/tplot_zoom.pro $

(See general/missions/rbsp/efw/utils/tplot_zoom.pro)


TPLOT_ZOOM_COM

[Previous Routine] [Next Routine] [List of Routines]
 NAME:
   tplot_zoom_com

 PURPOSE:


; Below is IDL code
ommon tplot_zoom_com, tbar, ybar, trange_stack, yzoom_vars, base

(See general/missions/rbsp/efw/utils/tplot_zoom_com.pro)


[4]

[Previous Routine] [List of Routines]
 NAME:

 PURPOSE:
   Retrieve a list of files on a remote directory accessible via http.

 CATEGORIES:
   Utilities

 CALLING SEQUENCE:
   result = jbt_fileurls(remote_dir, verbose = verbose)

     remote_dir must a valid http directory, such as:
     http://themis.ssl.berkeley.edu/data/rbsp/teams/spice/mk/

 ARGUMENTS:
   remote_dir: (In, required) See above.

 KEYWORDS:
   verbose: Set this keyword to 0 if one wants to suppress verbose screen
         output.

 COMMON BLOCKS:

 EXAMPLES:

 SEE ALSO:

 HISTORY:
   2012-10-27: Created by Jianbao Tao (JBT), SSL, UC Berkley.
   2012-11-02: Initial release to TDAS.


 VERSION:
 $LastChangedBy: jimm $
 $LastChangedDate: 2016-04-29 11:59:00 -0700 (Fri, 29 Apr 2016) $
 $LastChangedRevision: 20979 $
 $URL: svn+ssh://thmsvn@ambrosia.ssl.berkeley.edu/repos/spdsoft/tags/spedas_4_0/general/missions/rbsp/efw/utils/jbt_fileurls.pro $

(See general/missions/rbsp/efw/utils/jbt_fileurls.pro)