MathPack1 Documentation

by Phil Weichert

Contents


Introduction

Mathpack1 is a numerical analysis tookit. MathPack1 extends the Smalltalk environment by adding classes to support complex numbers, Vector (array of numbers) and matrices.   The classes added are:
ComplexNumbers
    ComplexNumber (Algebriac form a+bi)
    ComplexPolarForm (polar form r(cos (theta)+i sin(theta)))

Vector (array of numbers)

Matrices
    Matrices2Dimensional
        (groups all the two-dimension matrices)
    MatrixND
        (groups matrices with three or more dimensions)

There are a number of additional classes which are special types of matrices.
 

Each of the new class adds the basic operations such as addition(+), subtraction(-), and multiplication (*).  Within the new class a number of basic math functions have been.  Vector respond to mean, mediam, stardardDeviation, variances as well as a number of other useful functions.  Matrix responds to inverse, determinant, and many other operations.  Complex numbers know how to perform their basic math operations and a few common math functions.  These new classes were integrated that mixed mode arithmetic with the the classes is valid. NOTE: Matrices do not support "division".

NOTE: It is recommended that you review the comments in the source code of the examples and methods (both class and instance) for
additional information. You can also scan the Glossary located at the end of this manual for an explanation of additional terms used.
 

Examples
To demonstrate the use of a class and its methods, we have placed examples in the class methods of the new classes. Each example has comments explaining its purpose. The example methods are named exampleNN where NN is a two digit number from 01 to NN. These examples are designed to be evaluated in a workspace with 'print it.' For instance, to see the results of example03 in the class Matrix, evaluate the following line in a workspace with 'print it:'

    Matrix example03

NOTE: If the class browser does not list example0l, 02, 03, etc., the method named exampleReadMe will give the name of the class where examples are to be found. In addition, a number of 'test' methods have been added to the class methods of existing classes. The methods are prefixed with 'test' and do what the prefix says, "test the method." For example, added to class Float is testBeta which tests the beta function. Comments are included in each method explaining its purpose. As with examples, these test methods are designed to be evaluated in a workspace with 'print it.'
 
 

Go back to the top
 


Installation

To be done

Go back to the top


Complex Numbers

Overview

ComplexNumbers, a subclass of Magnitude, groups together the algebraic form (ComplexNumber) and polar form
(ComplexPolarForm). This choice was made because complex numbers properties differ significantly from real numbers (members of class Number). For instance, the inequality operations (< > etc.) are not defined for complex numbers. The ideal hierarchy would be:
Numbers
    RealNumbers (current class Number)
    ComplexNumbers

Class ComplexNumber uses the algebraic definition: (a + bi) where a is the real part, b is the imaginary part, and i is the square root of  -1.

Class ComplexPolarForm uses the polar form definition: r(cos(theta) + i sin(theta)) where r is the modulus (positive number), theta is the amplitude (angle in radians), and i is the square root of -1.
 

In this implementation, you should use instances of ComplexNumber for arithmetic operations (* + - / abs In exp. . .).
ComplexPolarForm is used primarily to find complex roots using De Moivre's theorem. The few arithmetic operations provided by ComplexPolarForm change the receiver to a ComplexNumber, perform the operation, and answer a ComplexNumber.

You can create of a ComplexNumber by sending an instance of Number the message imaginary:. For example, realPart imaginary: imaginaryPart where both realPart and imaginaryPart are Numbers. The shorter message i: has also been provided. You can use themessage cis: to create a complex number in polar form, ComplexPolarForm. For example, modulus cis: amplitude. You can make conversions between ComplexNumber and ComplexPolarForm by using the respective messages asComplexPolarForm and asComplexNumber.

When you use the arithmetic operators, * + - /, the result will always be an instance of ComplexNumber when one of the arguments is a complex number. Appropriate changes have been made to existing Number classes to support complex number arithmetic.

NOTE: These changes do not support operations with an instance of ComplexPolarForm.
 

ComplexNumber Method Highlights
The following list summarizes most of the common operations used in ComplexNumbers arithmetic operators, * + - /
amplitude
    Answers the angle in radians for the trigonometric form of the receiver.

asComplexPolarForm
    Answers the polar form of the receiver.

complexRoots: anInteger
    Answers a Vector with the n, nth roots of the receiver.

conjugate
    Answers the conjugate of the receiver.

exp
    Answers the exponential of the receiver.

imaginary
    Answers the imaginary part of the receiver.

In
    Answers the natural log of the receiver.

modulus
    Answers the modulus (absolute value) of the receiver.

raisedTo: aNumber
    Answers the result of the receiver raised to aNumber power.

real
    Answers the real part of the receiver.

A special version of complexRoots: is shown below as a class method of ComplexNumber

complexRootsOfUnity: anInteger
    Answers a Vector containing the n, nth roots of unity (1).
    (Special version of complexRoots:)
 

Go back to the top


Vectors

Overview

Vector, a subclass of Array, implements a special form of an array.

NOTE: While Arrays can contain many different types of objects, Vectors should contain ONLY numbers. Keep in mind, however, that Vector does not force you to use only numbers. Therefore, you must yourself ensure that the Vector subclass contains only numbers.

Another special property of Vectors is that the UndefinedObject nil is allowed in the vector for almost all methods. nil represents missing and/or invalid data values which are not to be used in computations. Missing/invalid values do occur in real-world statistical applications, especially in areas other than the social sciences.

The following is an example using nil. A Vector contains soil temperature measurements taken from various locations. A few
temperature values appear to be very high compared to the others. The high values could have been measurement errors or some other abnormality. Therefore, these high values may have biased the statistics. These values can be set to nil and the statistics recomputed to determine the amount of bias introduced by the high values. This technique maintains the original relationship of the measurements.

For example, if five different measurements were taken at each of 100 sites, the size of the temperature vector stays at 100 when one value is set to nil, meaning that the other four measurements for that location are still at the same relative index location. This results in significant reduction in bookkeeping.

NOTE: Arithmetic operations with a scalar are right-handed operations.
    Valid                    Wrong
    vector * scalar         scalar * vector

Using only right-handed operations requires no changes to the class Number or its subclasses, which results in no additional overhead for arithmetic operations (* + - /).

Vector Method Highlights
Arithmetic messages (* + - /) perform element-wise operations on the non-nil elements. The messages work with a Vector of the same size or a scalar.
 

The following list summarizes of the most common operations used in Vectors.

count
    Answers the number of non-nil elements.

minimum
    Answers the minimum value of the non-nil elements.

maximum
    Answers the maximum value of the non-nil elements.

mean
    Answers the mean (average) value of the non-nil elements.

median
    Answers the median value of the non-nil elements.

skewness
    Answers the skewness of non-nil values.

standard Deviation
    Answers the standard deviation of non-nil values.

variance
    Answers the variance of non-nil values.

kurtosis
    Answers the kurtosis of non-nil values.

moments
    Answers a dictionary containing: count, minimum,
    maximum, mean, median, variance, standardDeviation,
    absoluteDeviation, skewness, kurtosis.

Messages to Vector where Vector MUST NOT contain any nil elements are as follows:

vector * anObject
    Where anObject is a matrix (two-dimensional).

crossProduct: aVector

dotProduct: aVector
 

Go back to the top


Matrices

Overview

Matrices, the root class for all matrices, are subclassed by the number of dimensions into Matrices2Dimensional and MatrixND. The subclasses are as follows:

Matrices
    Matrices2Dimensional
                Groups the various forms of two-dimensional matrices.
                The subclasses are:
        LowerTriangularMatrix
        Matrix
           SquareMatrix
              LuMatrix
        TriDiagonalMatrix
    MatrixND
        For matrices with three or more dimensions. Has no subclasses.

Arithmetic operations expect the matrix to contain ONLY scalars. Otherwise, a matrix may contain any type of object.

NOTE: Matrix operations (* + - /) with a scalar are righthanded operations.
           Valid                            Wrong
            vector * scalar                 scalar * vector

Using only right-handed operations requires no changes to the class Number or its subclasses, which results in no additional overhead for arithmetic operations (* + - /).

You can access any form of Matrix through the methods defined for the specific type of matrix, Matrices2Dimensional or MatrixND (see the following sections). Methods at: and at:put: access an element at a linear position regardless of the dimensions of the matrix.
 

Go back to the top


Two Dimensional Matrices

All two dimensional matrices are a subclass of Matrices2Dimensional. To create one of the subclasses of Matrices2Dimensional, send the message new: aPoint or rows: numberOfRows columns: numberOfColumns to a subclass. When the message new: is used, aPoint is defined as the numberOfRows @ number0fColumns. Also, a
matrix may be created with a collection specified as its contents by the messages new:contents: or rows:columns:contents:. For Matrix and its subclasses, the collection size must be equal to numberOfRows times numberOfColumns. For a LowerTriangularMatrix and TridiagonalMatrix the numberOfRows also must equal the numberOfColumns. Let n represent the numberOfRows. For a LowerTriangularMatrix, the collection size must be equal (n * (n - 1)) / 2 + n. For a TridiagonalMatrix, the collection size must be equal to 3 * n - 2.

Examples:

• To create a matrix with 12 rows and 4 columns:
    Matrix new: 12 @ 4

• To create a matrix with 12 rows and 12 columns:
    Matrix new: 12 @ 12

NOTE: Because the number of rows equals the number of columns, a SquareMatrix is automatically created. This means that in order to create a new instance of a square or M @ N two-dimensional matrix, you always send the new: or new:contents: message to Class Matrix.
 

• To create a matrix with 3 rows and 3 columns and fill the contents with the given collection:
    Matrix new: 3 @ 3 contents: #(1 2 3 4 5 6 7 8 9)

The basic access methods for two-dimensional matrices are as follows:

row: rowNumber col: columnNumber
    Answers the element at the given row and column number.

row: rowNumber col: columnNumber put: anObject
    Places anObject at the given row and column number.

columnAt: columnNumber
    Answers a Vector containing the elements of the given columnNumber.
    Vector size equals the number of rows for the matrix.

columnAt: columnNumber put: aCollection
    Places the collection in the column specified by columnNumber.
    aCollection size must equal the number of rows for the matrix.

rowAt: rowNumber
    Answers a Vector containing the elements of the given rowNumber.
    Vector size equals the number of columns for the matrix.

rowAt: rowNumber put: aCollection
    Places the collection in the row specified by rowNumber.
    aCollection size must equal the number of columns for the matrix.
 

Two-Dimensional Matrices and Sub-Matrices
A number of manipulation methods exist for changing the structure of a matrix. Rows or columns may be inserted or removed. Sub-matrices may be extracted or replaced. A matrix may be appended at the right or bottom of an existing matrix. These methods are located in Matrices2Dimensional. They are as follows:

appendAtBottom: anArrayOrMatrix

appendAtRight: anArrayOrMatrix

deleteColumn: anIntegerOrArray

deleteRow: anIntegerOrArray

insertColumns: numberOfColumns before: columnNumber

insertRows: numberOfRows above: rowNumber

row: rowNumber col: columnNumber extractSubMatrix: dimensions

row: rowNumber col: columnNumber placeSubMatrix: aMatrix

See method comments for more explanation.

Matrix Method Highlights

The following list summarizes most of the common operations used in Matrices.
For an M @ N Matrix (M can equal N)

* aScalarVectorOrMatrix

+ aScalarOrMatrix

- aScalarOrMatrix

= aMatrix
    Answers true if the dimensions and contents are equal.

column: columnNumber1 exchange: columnNumber2
    Exchanges contents of columnNumber1 with columnNumber2.

row: rowNumber1 exchange: rowNumber2
    Exchanges contents of rowNumber1 with rowNumber2.

transpose
    Answers the transpose of the receiver.

For an N x N Matrix (class SquareMatrix)

determinant

inverse

jacobiEigenSystem
    Computes both the eigenvalues and eigenvectors of a
    real symmetric matrix by Jacobi transformations.

IuDecomposition
    Answers an LuMatrix containing the luDecomposition of the receiver.

realSymmetricEigenSystem: option
    Computes by QL method the eigenvalues and eigenvectors
    of a real symmetric matrix depending on the option chosen.
        If the option is  nil, both values and vectors are computed.
        If the option is non-nil, only eigenvalues are computed.

In LuMatrix

determinant

inverse

solveForMatrix: bMatrix
    Answers the solution matrix X for A * X = B
    where A is the receiver and B is the known matrix.

solveForVector: aVector
    Answers the solution vector x for A * x = b
    where A is the receiver and b is the known vector.

In TriDiagonalMatrix

computeReaISymmetricEigenSystem: option
    Computes by QL method the eigenvalues and eigenvectors
    of a real symmetric matrix depending on the option chosen.
    When the option is nil, both values and vectors are computed.
    When the option is non-nil, only eigenvalues are computed.

Various class example methods are available that demenstrate the matrix usuage..
 
 

Go back to the top


N-Dimension Matrices

Overview

MatrixND supports matrices with 3 or more dimensions. The creation methods are new: aDimensionVector or new:
aDimensionVector contents: aCollection. aDimensionVector can be an instance of Array or Vector. The total number of dimensions is aDimensionVector size. The contents of aDimensionVector are integer values representing the size of each dimension.

Examples:
• To create a matrix with four dimensions where the size of dimensions one through four are 6, 4,10, 9, respectively:
    MatrixND new: #(6 4 10 9)

• To create a three-dimensional matrix with the contents specified by a Collection:
    MatrixND new: #(2 2 2) contents: #(1 2 3 4 5 6 7 8)

NOTE: The collection size must equal the product of the dimension sizes.

In the preceding example, the collection size is 8, which equals 2*2*2.
 

The primary access methods for MatrixND are as follows:

elementAt: aVector
    Answers the element at the position given by the indices in aVector.
    aVector size must equal the number of dimensions for the MatrixND.

elementAt: aVector put: anObject
    Replaces the element at a position given by the indices in aVector with anObject.

rowAt: indicesVector
    Answers a vector containing the row. The desired row orientation
    is designated by the single zero position in the indicesVector.

rowAt: indicesVector put: aVector
    Places the contents of aVector in the desired row.
    The desired row orientation is designated by the single
    zero position in the indicesVector.

matrixAt: indicesVector
    Answers a matrix extracted from self. The desired matrix orientation
    is designated by two zero positions in the indicesVector.

matrixAt: indicesVector put: aMatrix
    Places aMatrix in self. The desired matrix orientation is designated
    by two zero positions in the indicesVector. aMatrix is assumed to
    be two-dimensional.
 

MatrixND Method Highlights

The following list summarizes most of the common operations used in MatrixND.

* aScalar

+ aScalarOrMatrix

- aScalarOrMatrix

= aMatrix
    Answers true if the dimensions and contents are equal.
 

Go back to the top


Additional Math Functions

A select set of functions was added to Number and its subclasses. These functions anticipate additional numerical methods which require them.  Because Smalltalk passes messages, the convention for passing arguments in MathPack1 appears strange compared to the mathematical notation. However, the convention used in MathPack1 is already used in Smalltalk. The convention is that the first argument in the function will receive the message followed by the remaining arguments.
        Math Notation                       Smalltalk Statement
        sin(x)                                      x sin
        ln(x)                                        x In
        functionName(x)                      x functionName
        functionName(x,y)                   x functionName: y
        functionName(a,b,x)                a functionName: b x: x

The math notation of a function is given in the comments of the functions.

Functions Included

Float additions:
beta: w
    Answers the value of the beta function defined as
    beta(z,w) = gamma(z)gamma(w) / gamma(z + w)
    where z is self.
   

betalncomplete: aValue b: bValue
    Answers the value of the incomplete beta function
    defined Ix(a,b), incomplete beta at x for values (a,b) where x is self.

    
 

errorFunction
    Answers the special case of the gammaIncomplete function
    errorFunction(x) = gammaIncomplete(0.5,x*x) where x is self.

    
 

errorFunctionComplement
    Answers the complementary error function associated
    with self errorFunctionComplement(x) = 1 - errorFunction(x)
    where x is self.

    
 

fRatioSignificance: numberDegreesOfFreedom1 f2: numberDegreesOfFreedom2
    Answers the significance of the f-ratio (self) with the two associated
    number of degrees of freedom. The f-ratio is the larger variance
    divided by the smaller variance of the two data vectors.

    numberDegreesOfFreedoml is associated with the larger variance
    and numberDegreesOfFreedom2 with the smaller variance. Degrees
    of freedom are the number of elements (nonnil) in the respective data vector less one.

    Answers with small values to indicate significantly different variances.
    (1.0 - answer) is the F-Distribution Probability Function value.
    (Used for computing F-Test for Significantly Different Variances.)

gammalncomplete: x
    Answers the value for gammaIncomplete(a,x) function where a is self.

    
 

gammalncompleteComplement: x
    Answers the value of gammaIncompleteComplement(a,x)function
    defined as gammaIncompleteComplement(a,x) = 1 - gammaIncomplete(a,x)
    where a is self.

    
 

gammaLn
    Answers the In of the gamma function on self.

    
 

Integer additions:

binomialCoefficient: k
    Answers the binomial coefficient | p | where 0 <= k <= n and n is self. k! (n-k)! where O>=k<=n
 

gammaLn
    Answers the In of the gamma function for an Integer value,  i.e. n factorial = gamma(n + 1)

    
 

Number routes the following messages to Float

beta: betalncomplete: errorFunction
errorFunctionComplement
gammaLn
gammalncomplete
gammalncompleteComplement
 

Go back to the top


Miscellaneous Additions

Formatted Printing

Methods were added to Number, ComplexNumber, Vector, and Matrices to allow formatted printing of numbers. The common message is #print0n: aStream width: aNumber decimal: numberOfPlaces. This message requests the receiver to print its contents in ASCII form on a stream at the current position. Each number printed will be right-justified in the specified width with the appropriate number of decimal places. Should the resulting number not fit, asterisks (***) will be printed.
Both Number and ComplexNumber support the additional message #printWidth:decimal. The receiver answers the ASCII string of the appropriate width with the specified number of decimal places.

NOTE: When the receiver is an instance of ComplexNumber, the length of the string is two times width plus two. The extra two is for 'i:'.

Similar messages have been provided for instances of String. They are as follows:

print0n: aStream width: anlnteger and
printWidth: anlnteger
        Left-justifies the string and pads the string with blanks on the right.

print0n: aStream rightWidth: anlnteger and
printRightWidth: anlnteger
        Right-justifies the string and pads on the left with blanks.

printWidth: anlnteger and
printRightWidth: anlnteger
    Answers a string of width anInteger with the left- and right-justification, respectively.

String asFloat
Method #asFloat converts a string containing the character representation of a number to an instance of class Float. The number may be in decimal notation or a notation. Valid strings are: '1', '1.2', '.2', '2e4', '1E-10'.

Example:
| vectorOfFIoatValues |
vectorOfFIoatValues := '1 .0 6.0 .1 e6' subStrings asVector asFloat.

The string is converted to a vector of float values. When lines in an ASCII file are numbers (blank delimited), this technique is useful.
 

Go back to the top


Summary of Existing Class Changes

To accommodate the new classes, several changes and additions have to be made to existing classes. Added math functions are not repeated in this section. A summary of the methods added or changed is shown below.

Collection
    asVector
    asMatrix
    asMatrix:

SequenceableCollection
    doIndex:
    findFirst:if None:

Number
    isScalar
    forceToZero:
    printOn:width:decirnal:
    printWidth:decimal:

Support for ComplexNumber
    asComplexNumber
    asComplexPolarForm
    cis:
    complexRoots:
    conjugate
    i:
    imaginary
    imaginary:
    pythagorean:
    real

Support for Matrices
    pseudoAbs
    signOf:

Object
    isScalar

String
    asFloat
    printOn:rightWidth:
    printOn:width:
    printRightWidth:
    printWidth:
 
 
 
 
 

Go back to the top
 


References

The references given below provide a sufficient set of material to gain an understanding of the functionality provided by MathPack1.  However, MathPack1 algorithms differ from those in the references. The differences are for the following reasons:
• Smalltalk is an object-oriented language (not procedural).
• The author respects the copyrighted material of others.

In cases where there are similarities, the mathematical derivations (formulas) dictate a similar algorithm. The conversion from radian to degrees or degrees to radians requires mathematically identical algorithms. This implies that any implementation will by nature strongly resemble any other implementation.

There are any number of references available for the functionality included in MathPack.  Therefor, only primary references used by the author are listed.
"Numerical Recipes" is strongly recommended as the best single source reference. Many of the books give an extensive list of additional references. These are not repeated here even though many of them were examined. The references are not listed in any particular order.

Numerical Recipes: The Art of Scientific Computing, William H. Press, Brian P. Flannery, Saul A. Teukolsky, William T. Vetterling. Cambridge University Press, 1988.

Collected Algorithms From ACM, multiple volumes. Association for Computing Machinery, Inc., 11 West 42nd Street, New York, New York, 10036.

Algorithms, second edition, Robert Sedgewick. Addision Wesley, 1988.

Fundamental Algorithms: The Art of Computer Programming, volume 1, second edition, Donald E. Knuth. Addison-Wesley, 1969.

Seminumerical Algorithms: The Art of Computer Programming, volume 2, second edition, Donald E. Knuth. Addison-Wesley, 1981.

CRC: Standard Mathematical Tables, Twenty-fourth Edition, William H. Beyer. CRC Press, 1976.

Linpack User's Guide, J.J. Dongarra, C.B. Moler, J.R. Bunch, G.W. Stewart. SIAM, 1979. (SIAM, 14th Floor, 117 South 17th Street, Philadelphia, PA 19103-5052.)

Lecture Notes in Computer Science; 6, Matrix Eigensystem Routines - EISPACK Guide, second edition, B.T. Smith et al,
Springer-Verlag 1976.

Lecture Notes in Computer Science; 51, Matrix Eigensystem Routines - EISPACK Guide Extension, B.S. Garbow et al.
Springer-Verlag, 1977.

Computational Methods in Elementary Numerical Analysis, John L. Morris. John Wiley & Sons, 1983.

Introduction to Matrices and Linear Transformations, second edition, Daniel T. Finkbeiner, II. W.H.Freeman and Company, 1965.

Chapters on Complex numbers from Algebra for College Students, Ross R. Middlemiss. McGraw-Hill Book Company, Inc., 1953; and Plane Trigonometry with Tables, third edition, E.Richard Heineman. McGraw-Hill Book Company, Inc., 1964.

Statistics and Data Analysis in Geology, John C. Davis. John Wiley & Sons, 1973.

Introduction to Statistical Analysis, third edition, Wilfrid J. Dixon, Frank J. Massey, Jr. McGraw-Hill Book Company, 1969.

Applied Regression Analysis, second edition, Norman Draper, Harry Smith. John Wiley & Sons, 1981.

Multivariate Data Analysis, William W. Cooley, Paul R. Lohnes. John Wiley & Sons, 1971
 

Go back to the top


Glossary

absolute value of a complex number - see modulus.

algebraic form of a complex number is defined by: (a + bi) where a is the real part, b is the imaginary part, and i is the square root of -1.

amplitude of a complex number (a + bi) is the angle theta equal arctan (b/a). Theta is used in the polar form.

ComplexNumbers - subclass of Magnitude containing common methods for its subclasses, ComplexNumber and ComplexPolarForm.

ComplexNumber class represents and manipulates the algebraic form of a complex number.

ComplexPolarForm class represents and manipulates the polar form of a complex number.

LowerTriangularMatrix class is a two-dimensional symmetrical matrix where only the lower half is stored. Dimensions are equal (n @ n) and total size equals (n * (n-1)) / 2+n.

LuMatrix class is a special form of SquareMatrix where the contents is the lu - decomposition of a matrix. Used to find the inverse, determinant, solve for a vector, and solve for a matrix.

Matrices class groups all matrices of two or more dimensions.

Matrices2Dimensional class groups matrices with two dimensions. Matrix class is the main class for matrices with 2 dimensions.

MatrixND class groups together matrices with 3 or more dimensions.

modulus of a complex number (a + bi) is also known as its absolute value. modulus equals square root of (a*a + b*b).

polar form of complex number is defined by: r(cos(theta) + i sin(theta)), where r is the modulus (positive number), theta is the amplitude (angle in radians), and i is the square root of -1.

real matrix means all the elements in the matrix are of class Number.

real symmetric matrix means that the matrix is real and symmetric.

scalar is an instance of Number (Integer, Fraction, or Float) or a ComplexNumber.

SquareMatrix is a subclass of Matrix where the number of rows equal the number of columns. The class exists to group a large number of matrix operations that are defined only for square matrices. System automatically creates a SquareMatrix when new: is sent to Matrix with an integer or point with x=y as an argument.

symmetrical matrix is dimensioned N by N and the elements a(i,j) = a(j,i) for all i=1..N and j=1..N except where i=j.

TriDiagonalMatrix class stores the three diagonals of a matrix. Elements not on one of the diagonals are considered to be zero. Dimensions are equal (n @ n) and total size equals 3 * n - 2.

trigonometric form of a complex number - see polar form.

Vector - a subclass of Array whose elements are scalars. When a vector contains any complex numbers, certain methods are invalid (e.g. #minimum, #maximum, #median which use inequality operators (< >)).
 

Go back to the top