Stability | experimental |
---|---|
Maintainer | Patrick Perry <patperry@stanford.edu> |
Immutable banded matrices.
- data Banded np e
- class (MatrixShaped a, HasVectorView a, HasMatrixStorage a, Elem e, BaseVector (VectorView a) e, BaseMatrix (MatrixStorage a) e) => BaseBanded a e where
- numLower :: a (n, p) e -> Int
- numUpper :: a (n, p) e -> Int
- bandwidths :: a (n, p) e -> (Int, Int)
- ldaBanded :: a (n, p) e -> Int
- transEnumBanded :: a (n, p) e -> TransEnum
- isHermBanded :: a (n, p) e -> Bool
- coerceBanded :: a np e -> a np' e
- maybeMatrixStorageFromBanded :: a (n, p) e -> Maybe (MatrixStorage a (k, p) e)
- maybeBandedFromMatrixStorage :: (Int, Int) -> (Int, Int) -> MatrixStorage a (k, p) e -> Maybe (a (n, p) e)
- module Data.Matrix.Class
- module Data.Matrix.Class.IMatrix
- banded :: BLAS3 e => (Int, Int) -> (Int, Int) -> [((Int, Int), e)] -> Banded (n, p) e
- listsBanded :: BLAS3 e => (Int, Int) -> (Int, Int) -> [[e]] -> Banded (n, p) e
- zeroBanded :: BLAS3 e => (Int, Int) -> (Int, Int) -> Banded (n, p) e
- constantBanded :: BLAS3 e => (Int, Int) -> (Int, Int) -> e -> Banded (n, p) e
- bandedFromVector :: Elem e => (Int, Int) -> Vector k e -> Banded (n, p) e
- diagBandedFromVector :: Elem e => Vector n e -> Banded (n, n) e
- maybeVectorFromBanded :: Elem e => Banded (n, p) e -> Maybe (Vector k e)
- diagBanded :: BLAS1 e => Banded (n, p) e -> Int -> Vector k e
- module Data.Tensor.Class
- module Data.Tensor.Class.ITensor
Banded matrix type
Immutable banded matrices. The type arguments are as follows:
-
np
: a phantom type for the shape of the matrix. Most functions will demand that this be specified as a pair. When writing a function signature, you should always preferBanded (n,p) e
toBanded np e
. -
e
: the element type of the matrix. Only certain element types are supported.
MatrixShaped Banded | |
HasMatrixStorage Banded | |
HasVectorView Banded | |
BLAS3 e => IMatrix Banded e | |
Elem e => BaseBanded Banded e | |
BLAS3 e => MMatrix Banded e IO | |
BLAS3 e => ReadBanded Banded e IO | |
BLAS3 e => MMatrix Banded e (ST s) | |
BLAS3 e => ReadBanded Banded e (ST s) | |
Shaped Banded (Int, Int) | |
BLAS3 e => ITensor Banded (Int, Int) e | |
(BLAS3 e, Monad m) => ReadTensor Banded (Int, Int) e m | |
BLAS3 e => IMatrix (Herm Banded) e | |
BLAS3 e => IMatrix (Tri Banded) e | |
BLAS3 e => ISolve (Tri Banded) e | |
BLAS3 e => MSolve (Tri Banded) e IO | |
BLAS3 e => MMatrix (Herm Banded) e IO | |
BLAS3 e => MMatrix (Tri Banded) e IO | |
BLAS3 e => MSolve (Tri Banded) e (ST s) | |
BLAS3 e => MMatrix (Herm Banded) e (ST s) | |
BLAS3 e => MMatrix (Tri Banded) e (ST s) | |
(BLAS3 e, Eq e) => Eq (Banded (n, p) e) | |
BLAS3 e => Show (Banded (n, p) e) | |
(BLAS3 e, AEq e) => AEq (Banded (n, p) e) |
Overloaded interface for banded matrices
class (MatrixShaped a, HasVectorView a, HasMatrixStorage a, Elem e, BaseVector (VectorView a) e, BaseMatrix (MatrixStorage a) e) => BaseBanded a e whereSource
Common functionality for all banded matrix types.
numLower :: a (n, p) e -> IntSource
Get the number of lower diagonals in the banded matrix.
numUpper :: a (n, p) e -> IntSource
Get the number of upper diagonals in the banded matrix
bandwidths :: a (n, p) e -> (Int, Int)Source
Get the range of valid diagonals in the banded matrix.
bandwidthds a
is equal to (numLower a, numUpper a)
.
ldaBanded :: a (n, p) e -> IntSource
Get the leading dimension of the underlying storage of the banded matrix.
transEnumBanded :: a (n, p) e -> TransEnumSource
Get the storage type of the banded matrix.
isHermBanded :: a (n, p) e -> BoolSource
Indicate whether or not the banded matrix storage is transposed and conjugated.
coerceBanded :: a np e -> a np' eSource
Cast the shape type of the banded matrix.
maybeMatrixStorageFromBanded :: a (n, p) e -> Maybe (MatrixStorage a (k, p) e)Source
Get a matrix with the underlying storage of the banded matrix. This will fail if the banded matrix is hermed.
maybeBandedFromMatrixStorage :: (Int, Int) -> (Int, Int) -> MatrixStorage a (k, p) e -> Maybe (a (n, p) e)Source
Given a shape and bandwidths, possibly view the elements stored in a dense matrix as a banded matrix. This will if the matrix storage is hermed. An error will be called if the number of rows in the matrix does not equal the desired number of diagonals or if the number of columns in the matrix does not equal the desired number of columns.
Elem e => BaseBanded IOBanded e | |
Elem e => BaseBanded Banded e | |
Elem e => BaseBanded (STBanded s) e |
Overloaded interface for matrices
module Data.Matrix.Class
module Data.Matrix.Class.IMatrix
Creating banded matrices
banded :: BLAS3 e => (Int, Int) -> (Int, Int) -> [((Int, Int), e)] -> Banded (n, p) eSource
Create a banded matrix with the given shape, bandwidths, and associations. The indices in the associations list must all fall in the bandwidth of the matrix. Unspecified elements will be set to zero.
listsBanded :: BLAS3 e => (Int, Int) -> (Int, Int) -> [[e]] -> Banded (n, p) eSource
Create a banded matrix of the given shape and bandwidths by specifying
its diagonal elements. The lists must all have the same length, equal
to the number of elements in the main diagonal of the matrix. The
sub-diagonals are specified first, then the super-diagonals. In
subdiagonal i
, the first i
elements of the list are ignored.
Special banded matrices
zeroBanded :: BLAS3 e => (Int, Int) -> (Int, Int) -> Banded (n, p) eSource
Create a zero banded matrix with the specified shape and bandwidths.
constantBanded :: BLAS3 e => (Int, Int) -> (Int, Int) -> e -> Banded (n, p) eSource
Create a constant banded matrix of the specified shape and bandwidths.
Conversions between vectors and banded matrices
bandedFromVector :: Elem e => (Int, Int) -> Vector k e -> Banded (n, p) eSource
Create a banded matrix from a vector. The vector must have length equal to one of the specified dimension sizes.
diagBandedFromVector :: Elem e => Vector n e -> Banded (n, n) eSource
Create a diagonal banded matrix from a vector.
maybeVectorFromBanded :: Elem e => Banded (n, p) e -> Maybe (Vector k e)Source
Convert a diagonal banded matrix to a vector. Fail if the banded matrix has more than one diagonal
Vector views
diagBanded :: BLAS1 e => Banded (n, p) e -> Int -> Vector k eSource
Get a the given diagonal in a banded matrix. Negative indices correspond to sub-diagonals.
Overloaded interface for reading banded matrix elements
module Data.Tensor.Class
module Data.Tensor.Class.ITensor