Back to library index.

Package std-array (in std.i) - building and manipulating arrays

Index of documented functions or symbols:

accum_dimlist

DOCUMENT accum_dimlist, dims, d
  accumulate a dimension argument D onto a dimension list DIMS.
  This can be used to emulate the dimension lists supplied to the
  array function.  For example:
func myfunc
      local dims;
      while (more_args()) accum_dimlist, dims, next_arg();
      ...
    }

SEE ALSO: array, reform

allof

DOCUMENT allof(x)
         anyof(x)
         nallof(x)
         noneof(x)
  Respectively:
   returns 1 if every element of the array x is non-zero, else 0.
   returns 1 if at least one element of the array x is non-zero, else 0.
   returns 1 if at least one element of the array x is zero, else 0.
   returns 1 if every element of the array x is zero, else 0.

SEE ALSO: allof, anyof, noneof, nallof, where, where2

anyof

SEE: allof

array

DOCUMENT array(value, dimension_list)
      or array(type, dimension_list)
  returns an object of the same type as VALUE, consisting of copies
  of VALUE, with the given DIMENSION_LIST appended to the dimensions
  of VALUE.  Hence, array(1.5, 3, 1) is the same as [[1.5, 1.5, 1.5]].
  In the second form, the VALUE is taken as scalar zero of the TYPE.
  Hence, array(short, 2, 3) is the same as [[0s,0s],[0s,0s],[0s,0s]].
  A DIMENSION_LIST is a list of arguments, each of which may be
  any of the following:
     (1) A positive scalar integer expression,
     (2) An index range with no step field (e.g.-  1:10), or
     (3) A vector of integers [number of dims, length1, length2, ...]
         (that is, the format returned by the dimsof function).

SEE ALSO: reshape, is_array, dimsof, numberof, grow, span, use_origins, _lst

avg

DOCUMENT avg(x)
  returns the scalar average of all elements of its array argument.

SEE ALSO: sum, min, max

digitize

DOCUMENT digitize(x, bins)
  returns an array of longs with dimsof(X), and values i such that
  BINS(i-1) <= X < BINS(i) if BINS is monotonically increasing, or
  BINS(i-1) > X >= BINS(i) if BINS is monotonically decreasing.
  Beyond the bounds of BINS, returns either i=1 or i=numberof(BINS)+1
  as appropriate.

SEE ALSO: histogram, interp, integ, sort, where, where2

grow

DOCUMENT grow, x, xnext1, xnext2, ...
      or grow(x, xnext1, xnext2, ...)
      or    _(x, xnext1, xnext2, ...)
  lengthens the array X by appending XNEXT1, XNEXT2, etc. to its
  final dimension.  If X is nil, X is first redefined to the first
  non-nil XNEXT, and the remainder of the XNEXT list is processed
  normally.  Each XNEXT is considered to have the same number of
  dimensions as X, by appending unit-length dimensions if necessary.
  All but this final dimension of each XNEXT must be right-conformable
  (that is, conformable in the sense of the right hand side of an
  assignment statement) with all but the final dimension of X.
  The result has a final dimension which is the sum of the final
  dimension of X and all the final dimensions of the XNEXT.  Nil
  XNEXT are ignored.  The value of the result is obtained by
  concatenating all the XNEXT to X, after any required broadcasts.

  If invoked as a function, grow returns the new value of X; in
  this case, X may be an expression.  X must be a simple variable
  reference for the subroutine form of grow; otherwise there is
  nowhere to return the result.  The subroutine form is slightly
  more efficient than the function form for the common usage:
       x= grow(x, xnext1, xnext2)           is the same as
       grow, x, xnext1, xnext2              the preferred form

  The _ function is a synonym for grow, for people who want this
  operator to look like punctuation in their source code, on analogy
  with the array building operator [a, b, c, ...].

  The _cat function is sometimes more appropriate than grow.

  Usage note:
  Never do this:
    while (more_data) grow, result, datum;
  The time to complete this loop scales as the SQUARE of the number
  of passes!  Instead, do this:
    for (i=1,result=array(things,n_init) ; more_data ; i++) {
      if (i>numberof(result)) grow, result, result;
      result(i) = datum;
    }
    result = result(1:i-1);
  The time to complete this loop scales as n*log(n), because the
  grow operation doubles the length of the result each time.

SEE ALSO: _cat, array

histinv

DOCUMENT list = histinv(hist)
  returns a list whose histogram is HIST, hist = histogram(list),
  that is, hist(1) 1's followed by hist(2) 2's, followed by hist(3)
  3's, and so on.  The total number of elements in the returned
  list is sum(hist).  All values in HIST must be non-negative;
  if sum(hist)==0, histinv returns [].  The input HIST array may
  have any number of dimensions; the result will always be either
  nil or a 1D array.

SEE ALSO: histogram

histogram

DOCUMENT histogram(list)
      or histogram(list, weight)
  returns an array hist which counts the number of occurrences of each
  element of the input index LIST, which must consist of positive
  integers (1-origin index values into the result array):
       histogram(list)(i) = number of occurrences of i in LIST

  A second argument WEIGHT must have the same shape as LIST; the result
  will be the sum of WEIGHT:
       histogram(list)(i) = sum of all WEIGHT(j) where LIST(j)==i

  The result of the single argument call will be of type long; the
  result of the two argument call will be of type double (WEIGHT is
  promoted to that type).  The input argument(s) may have any number
  of dimensions; the result is always 1-D.

KEYWORD: top=max_list_value
  By default, the length of the result is max(LIST).  You may
  specify that the result have a larger length by means of the TOP
  keyword.  (Elements beyond max(LIST) will be 0, of course.)

SEE ALSO: digitize, sort, histinv

indgen

DOCUMENT indgen(n)
      or indgen(start:stop)
      or indgen(start:stop:step)
  returns "index generator" list -- an array of longs running from
  1 to N, inclusive.  In the second and third forms, the index
  values specified by the index range are returned.

SEE ALSO: span, spanl, array

integ

DOCUMENT integ(y, x, xp)
      or integ(y, x, xp, which)
  See the interp function for an explanation of the meanings of the
  arguments.  The integ function returns ypi which is the integral
  of the piecewise linear curve (X(i), Y(i)) (i=1, ..., numberof(X))
  from X(1) to XP.  The curve (X, Y) is regarded as constant outside
  the bounds of X.  Note that X must be monotonically increasing or

SEE ALSO: interp, digitize, span

interp

DOCUMENT interp(y, x, xp)
      or interp(y, x, xp, which)
  returns yp such that (XP, yp) lies on the piecewise linear curve
  (X(i), Y(i)) (i=1, ..., numberof(X)).  Points beyond X(1) are set
  to Y(1); points beyond X(0) are set to Y(0).  The array X must be
  one dimensional, have numberof(X)>=2, and be either monotonically
  increasing or monotonically decreasing.  The array Y may have more
  than one dimension, but dimension WHICH must be the same length as
  X.  WHICH defaults to 1, the first dimension of Y.  WHICH may be
  non-positive to count dimensions from the end of Y; a WHICH of 0
  means the final dimension of Y.  The result yp has dimsof(XP)
  in place of the WHICH dimension of Y (if XP is scalar, the WHICH
  dimension is not present).  (The dimensions of the result are the
  same as if an index list with dimsof(XP) were placed in slot
  WHICH of Y.)

SEE ALSO: integ, digitize, span

max

DOCUMENT max(x)
      or max(x, y, z, ...)
  returns the scalar maximum value of its array argument, or, if
  more than one argument is supplied, returns an array of the
  maximum value for each array element among the several arguments.
  In the multi-argument case, the arguments must be conformable.

SEE ALSO: min, sum, avg

median

DOCUMENT median(x)
      or median(x, which)
  returns the median of the array X.  The search for the median takes
  place along the dimension of X specified by WHICH.  WHICH defaults
  to 1, meaning the first index of X.  The median function returns an
  array with one fewer dimension than its argument X (the WHICH
  dimension of X is missing in the result), in exact analogy with
  rank reducing index range functions.  If dimsof(X)(WHICH) is
  odd, the result will have the same data type as X; if even, the
  result will be a float or a double, since the median is defined
  as the arithmetic mean between the two central values in that
  case.

SEE ALSO: sort

merge

DOCUMENT merge(true_expr, false_expr, condition)
  returns the values TRUE_EXPR or FALSE_EXPR where CONDITION is
  non-zero or zero, respectively.  The result has the data type of
  TRUE_EXPR or FALSE_EXPR, promoted to the higher arithmetic type
  if necessary.  The result has the dimensions of CONDITION.
  The number of elements in TRUE_EXPR must match the number of
  non-zero elements of CONDITION, and the number of elements in
  FALSE_EXPR must match the number of zero elements of CONDITION.
  (TRUE_EXPR or FALSE_EXPR should be nil if there are no such
  elements of CONDITION.  Normally, TRUE_EXPR and FALSE_EXPR should
  be 1-D arrays if they are not nil.)
  This function is intended for vectorizing a function whose
  domain is divided into two or more parts, as in:
func f
       big= (x>=threshhold);
       wb= where(big);
       ws= where(!big);
       if (is_array(wb)) {
         xx= x(wb);
         fb= 
       }
       if (is_array(ws)) {
         xx= x(ws);
         fs= 
       }
       return merge(fb, fs, big);
     }

SEE ALSO: mergef, merge2, where

merge2

DOCUMENT merge2(true_expr, false_expr, condition)
  returns the values TRUE_EXPR or FALSE_EXPR where CONDITION is
  non-zero or zero, respectively.  The result has the data type of
  TRUE_EXPR or FALSE_EXPR, promoted to the higher arithmetic type
  if necessary.  Unlike the merge function, TRUE_EXPR and FALSE_EXPR
  must be conformable with each other, and with the CONDITION.

SEE ALSO: merge, where, mergef

mergef

DOCUMENT y = mergef(x, f1, cond1, f2, cond2, ... felse)
  Evaluate F1(X(where(COND1))), F2(X(where(COND2))),
  and so on, until FELSE(X(where(!(COND1 | COND2 | ...))))
  and merge all the results back into an array Y with the
  same dimensions as X.  Each of the CONDi must have the
  same dimensions as X, and they must be mutally exclusive.

  During the evaluation of Fi, all of the local variables of
  the caller of mergei are available.  The Fi are called in
  order, skipping any for which no X is in the specified interval.
  Each Fi must return a double value with the same dimensions as
  its input.

  Additional input and output variables can be constructed using
  the mergel index list employed by mergei, and using the mergeg
  function.  For example, let w be an additional input to and z be
  an additional output from the function:
    func myfunc(x, w, &z) {
      z = array(0.0, dimsof(x, w));
      x += z;
      w += z;
      return mergef(x, _myfunc_lo, x<1.234, _myfunc_hi);
    }
    func _myfunc_lo(x) {
      wp = w(mergel);  // part of w for this function
      z = mergeg(z, );
      return ;
    }
    func _myfunc_hi(x) {
      wp = w(mergel);  // part of w for this function
      z = mergeg(z, );
      return ;
    }

SEE ALSO: mergei, merge

mergeg

DOCUMENT z = mergeg(z, value)
      or z = mergeg(z)
  If secondary results are to be returned from a mergef, besides
  its return value, the Fi may construct them using mergeg.
    z = mergeg(z, value)
  where z is a variable in the original caller of mergef,
  and value is its value.

  z = [];    or   z = ;
  y = mergef(x, f1, cond, f2);
  z = mergeg(z);  // this can now be omitted, but does no harm
  ...
  func f1(x) { 
    z = mergeg(z, exprz(x));
    return expry(x);
  }
  func f2(x) { 
    z = mergeg(z, exprz(x));
    return expry(x);
  }

SEE ALSO: mergef, merge

mergei

DOCUMENT y = mergei(x, f0, x1, f1, x2, ... xN, fN)
  Evaluate F1 where X=XN,
  and merge all the results back into an array Y with the
  same dimensions as X.

  During the evaluation of Fi, all of the local variables of
  the caller of mergei are available.  The Fi are called in
  order, skipping any for which no X is in the specified interval.
  Each Fi must return a value with the same dimensions as
  its input.

  Additional input and output variables can be constructed using
  the mergel index list employed by mergei, and using the mergeg
  function.  For example, let w be an additional input to and z be
  an additional output from the function:
    func myfunc(x, w, &z) {
      z = array(0.0, dimsof(x, w));
      x += z;
      w += z;
      return mergei(x, _myfunc_lo, 1.234, _myfunc_hi);
    }
    func _myfunc_lo(x) {
      wp = w(mergel);  // part of w for this function
      z = mergeg(z, );
      return ;
    }
    func _myfunc_hi(x) {
      wp = w(mergel);  // part of w for this function
      z = mergeg(z, );
      return ;
    }

SEE ALSO: mergef, merge

min

DOCUMENT min(x)
      or min(x, y, z, ...)
  returns the scalar minimum value of its array argument, or, if
  more than one argument is supplied, returns an array of the
  minimum value for each array element among the several arguments.
  In the multi-argument case, the arguments must be conformable.

SEE ALSO: max, sum, avg

nallof

SEE: allof

noneof

SEE: allof

reform

DOCUMENT reform(x, dimlist)
   returns array X reshaped according to dimension list DIMLIST.

SEE ALSO: array, dimsof, accum_dimlist

reshape

DOCUMENT reshape, reference, address, type, dimension_list
      or reshape, reference, type, dimension_list
      or reshape, reference
  The REFERENCE must be an unadorned variable, not an expression;
  reshape sets this variable to an LValue at the specified ADDRESS
  with the specified TYPE and DIMENSION_LIST.  (See the array
  function documentation for acceptable DIMENSION_LIST formats.)
  If ADDRESS is an integer (e.g.- a long), the programmer is
  responsible for assuring that the data at ADDRESS is valid.
  If ADDRESS is a (Yorick) pointer, Yorick will assure that the
  data pointed to will not be discarded, and the reshape will
  fail if TYPE and DIMENSION_LIST extend beyond the pointee
  bounds.  In the second form, ADDRESS is taken to be &REFERENCE;
  that is, the TYPE and DIMENSION_LIST of the variable are changed
  without doing any type conversion.  In the third form, REFERENCE
  is set to nil ([]).  (Simple redefinition will not work on a
  variable defined using reshape.)
  WARNING: There are almost no situations for which reshape is
    the correct operation.  Use reform instead.

SEE ALSO: reform, array, dimsof, numberof, is_array, eq_nocopy

sort

DOCUMENT sort(x)
      or sort(x, which)
  returns an array of longs with dimsof(X) containing index values
  such that X(sort(X)) is a monotonically increasing array.  X can
  contain integer, real, or string values.  If X has more than one
  dimension, WHICH determines the dimension to be sorted.  The
  default WHICH is 1, corresponding to the first dimension of X.
  WHICH can be non-positive to count dimensions from the end of X;
  in particular a WHICH of 0 will sort the final dimension of X.

  WARNING: The sort function is non-deterministic if some of the
           values of X are equal, because the Quick Sort algorithm
           involves a random selection of a partition element.

  For information on sorting with multiple keys (and on making
  sort deterministic), type the following:
     #include "msort.i"
     help, msort

SEE ALSO: median, digitize, interp, integ, histogram

span

DOCUMENT span(start, stop, n)
      or span(start, stop, n, which)
  returns array of N doubles equally spaced from START to STOP.
  The START and STOP arguments may themselves be arrays, as long as
  they are conformable.  In this case, the result will have one
  dimension of length N in addition to dimsof(START, STOP).
  By default, the result will be N-by-dimsof(START, STOP), but
  if WHICH is specified, the new one of length N will be the
  WHICHth.  WHICH may be non-positive to position the new
  dimension relative to the end of dimsof(START, STOP); in
  particular WHICH of 0 produces a result with dimensions
  dimsof(START, STOP)-by-N.

SEE ALSO: spanl, indgen, array

spanl

DOCUMENT spanl(start, stop, n)
      or spanl(start, stop, n, which)
  similar to the span function, but the result array have N points
  spaced at equal ratios from START to STOP (that is, equally
  spaced logarithmically).  See span for discussion of WHICH argument.
  START and STOP must have the same algebraic sign for this to make
  any sense.

SEE ALSO: span, indgen, array

sum

DOCUMENT sum(x)
  returns the scalar sum of all elements of its array argument.
  If X is a string, concatenates all elements.

SEE ALSO: avg, min, max

transpose

DOCUMENT transpose(x)
      or transpose(x, permutation1, permutation2, ...)
  transpose the first and last dimensions of array X.  In the second
  form, each PERMUTATION specifies a simple permutation of the
  dimensions of X.  These permutations are compounded left to right
  to determine the final permutation to be applied to the dimensions
  of X.  Each PERMUTATION is either an integer or a 1D array of
  integers.  A 1D array specifies a cyclic permutation of the
  dimensions as follows: [3, 5, 2] moves the 3rd dimension to the
  5th dimension, the 5th dimension to the 2nd dimension, and the 2nd
  dimension to the 3rd dimension.  Non-positive numbers count from the
  end of the dimension list of X, so that 0 is the final dimension,
  -1 in the next to last, etc.  A scalar PERMUTATION is a shorthand
  for a cyclic permutation of all of the dimensions of X.  The value
  of the scalar is the dimension to which the 1st dimension will move.

  Examples:  Let x have dimsof(x) equal [6, 1,2,3,4,5,6] in order
     to be able to easily identify a dimension by its length. Then:
     dimsof(x)                          == [6, 1,2,3,4,5,6]
     dimsof(transpose(x))               == [6, 6,2,3,4,5,1]
     dimsof(transpose(x,[1,2]))         == [6, 2,1,3,4,5,6]
     dimsof(transpose(x,[1,0]))         == [6, 6,2,3,4,5,1]
     dimsof(transpose(x,2))             == [6, 6,1,2,3,4,5]
     dimsof(transpose(x,0))             == [6, 2,3,4,5,6,1]
     dimsof(transpose(x,3))             == [6, 5,6,1,2,3,4]
     dimsof(transpose(x,[4,6,3],[2,5])) == [6, 1,5,6,3,2,4]

where

DOCUMENT where(x)
  returns the vector of longs which is the index list of non-zero
  values in the array x.  Thus, where([[0,1,3],[2,0,4]]) would
  return [2,3,4,6].  If noneof(x), where(x) is a special range
  function which will return a nil value if used to index an array;
  hence, if noneof(x), then x(where(x)) is nil.
  If x is a non-zero scalar, then where(x) returns a scalar value.
  The rather recondite behavior for scalars and noneof(x) provides
  maximum performance when the merge function to be used with the
  where function.

SEE ALSO: where2, merge, merge2, allof, anyof, noneof, nallof, sort

where2

DOCUMENT where2(x)
  like where(x), but the returned list is decomposed into indices
  according to the dimensions of x.  The returned list is always
  2 dimensional, with the second dimension the same as the dimension
  of where(x).  The first dimension has length corresponding to the
  number of dimensions of x.  Thus, where2([[0,1,3],[2,0,4]]) would
  return [[2,1],[3,1],[1,2],[3,2]].
  If noneof(x), where2 returns [] (i.e.- nil).

SEE ALSO: where, merge, merge2, allof, anyof, noneof, nallof, sort

_

SEE: grow