Stability | experimental |
---|---|
Maintainer | Patrick Perry <patperry@stanford.edu> |
- Banded matrix type classes
- Overloaded interface for matrices
- Creating banded matrices
- Special banded matrices
- Copying banded matrices
- Conversions between banded matrices and vectors
- Row and column views
- Getting diagonals
- Overloaded interface for reading and writing banded matrix elements
- Conversions between mutable and immutable banded matrices
- Conversions from
IOBanded
s
An overloaded interface to mutable banded matrices. For matrix types than can be used with this interface, see Data.Matrix.Banded.IO and Data.Matrix.Banded.ST. Many of these functions can also be used with the immutable type defined in Data.Matrix.Banded.
- 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)
- viewVectorAsBanded :: (Int, Int) -> VectorView a k e -> a (n, p) e
- viewVectorAsDiagBanded :: VectorView a n e -> a (n, n) e
- maybeViewBandedAsVector :: a (n, p) e -> Maybe (VectorView a k e)
- unsafeBandedToIOBanded :: a (n, p) e -> IOBanded (n, p) e
- class (BaseBanded a e, BLAS2 e, ReadTensor a (Int, Int) e m, MMatrix a e m, MMatrix (Herm a) e m, MMatrix (Tri a) e m, MSolve (Tri a) e m, ReadVector (VectorView a) e m, ReadMatrix (MatrixStorage a) e m) => ReadBanded a e m where
- unsafePerformIOWithBanded :: a (n, p) e -> (IOBanded (n, p) e -> IO r) -> m r
- freezeBanded :: a (n, p) e -> m (Banded (n, p) e)
- unsafeFreezeBanded :: a (n, p) e -> m (Banded (n, p) e)
- class (ReadBanded a e m, WriteTensor a (Int, Int) e m, WriteVector (VectorView a) e m, WriteMatrix (MatrixStorage a) e m) => WriteBanded a e m where
- newBanded_ :: (Int, Int) -> (Int, Int) -> m (a (n, p) e)
- unsafeConvertIOBanded :: IO (IOBanded (n, p) e) -> m (a (n, p) e)
- thawBanded :: Banded (n, p) e -> m (a (n, p) e)
- unsafeThawBanded :: Banded (n, p) e -> m (a (n, p) e)
- module Data.Matrix.Class
- module Data.Matrix.Class.MMatrix
- newBanded :: WriteBanded a e m => (Int, Int) -> (Int, Int) -> [((Int, Int), e)] -> m (a (n, p) e)
- newListsBanded :: WriteBanded a e m => (Int, Int) -> (Int, Int) -> [[e]] -> m (a (n, p) e)
- newZeroBanded :: WriteBanded a e m => (Int, Int) -> (Int, Int) -> m (a (n, p) e)
- setZeroBanded :: WriteBanded a e m => a (n, p) e -> m ()
- newConstantBanded :: WriteBanded a e m => (Int, Int) -> (Int, Int) -> e -> m (a (n, p) e)
- setConstantBanded :: WriteBanded a e m => e -> a (n, p) e -> m ()
- newCopyBanded :: (ReadBanded a e m, WriteBanded b e m) => a (n, p) e -> m (b (n, p) e)
- copyBanded :: (WriteBanded b e m, ReadBanded a e m) => b (n, p) e -> a (n, p) e -> m ()
- rowViewBanded :: BaseBanded a e => a (n, p) e -> Int -> (Int, VectorView a k e, Int)
- colViewBanded :: BaseBanded a e => a (n, p) e -> Int -> (Int, VectorView a k e, Int)
- diagViewBanded :: BaseBanded a e => a (n, p) e -> Int -> VectorView a k e
- getDiagBanded :: (ReadBanded a e m, WriteVector y e m) => a (n, p) e -> Int -> m (y k e)
- module Data.Tensor.Class
- module Data.Tensor.Class.MTensor
Banded matrix type classes
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.
viewVectorAsBanded :: (Int, Int) -> VectorView a k e -> a (n, p) eSource
View a vector as a banded matrix of the given shape. The vector must have length equal to one of the specified dimensions.
viewVectorAsDiagBanded :: VectorView a n e -> a (n, n) eSource
View a vector as a diagonal banded matrix.
maybeViewBandedAsVector :: a (n, p) e -> Maybe (VectorView a k e)Source
If the banded matrix has only a single diagonal, return a view
into that diagonal. Otherwise, return Nothing
.
unsafeBandedToIOBanded :: a (n, p) e -> IOBanded (n, p) eSource
Unsafe cast from a matrix to an IOBanded
.
Elem e => BaseBanded IOBanded e | |
Elem e => BaseBanded Banded e | |
Elem e => BaseBanded (STBanded s) e |
class (BaseBanded a e, BLAS2 e, ReadTensor a (Int, Int) e m, MMatrix a e m, MMatrix (Herm a) e m, MMatrix (Tri a) e m, MSolve (Tri a) e m, ReadVector (VectorView a) e m, ReadMatrix (MatrixStorage a) e m) => ReadBanded a e m whereSource
Banded matrices that can be read in a monad.
unsafePerformIOWithBanded :: a (n, p) e -> (IOBanded (n, p) e -> IO r) -> m rSource
Cast the banded matrix to an IOBanded
, perform an IO
action, and
convert the IO
action to an action in the monad m
. This
operation is very unsafe.
freezeBanded :: a (n, p) e -> m (Banded (n, p) e)Source
Convert a mutable banded matrix to an immutable one by taking a complete copy of it.
unsafeFreezeBanded :: a (n, p) e -> m (Banded (n, p) e)Source
BLAS3 e => ReadBanded IOBanded e IO | |
BLAS3 e => ReadBanded Banded e IO | |
BLAS3 e => ReadBanded Banded e (ST s) | |
BLAS3 e => ReadBanded (STBanded s) e (ST s) |
class (ReadBanded a e m, WriteTensor a (Int, Int) e m, WriteVector (VectorView a) e m, WriteMatrix (MatrixStorage a) e m) => WriteBanded a e m whereSource
Banded matrices that can be created or modified in a monad.
newBanded_ :: (Int, Int) -> (Int, Int) -> m (a (n, p) e)Source
Creates a new banded matrix of the given shape and bandwidths. The elements will be uninitialized.
unsafeConvertIOBanded :: IO (IOBanded (n, p) e) -> m (a (n, p) e)Source
thawBanded :: Banded (n, p) e -> m (a (n, p) e)Source
Convert an immutable banded matrix to a mutable one by taking a complete copy of it.
unsafeThawBanded :: Banded (n, p) e -> m (a (n, p) e)Source
BLAS3 e => WriteBanded IOBanded e IO |
Overloaded interface for matrices
module Data.Matrix.Class
module Data.Matrix.Class.MMatrix
Creating banded matrices
newBanded :: WriteBanded a e m => (Int, Int) -> (Int, Int) -> [((Int, Int), e)] -> m (a (n, p) e)Source
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.
newListsBanded :: WriteBanded a e m => (Int, Int) -> (Int, Int) -> [[e]] -> m (a (n, p) e)Source
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
newZeroBanded :: WriteBanded a e m => (Int, Int) -> (Int, Int) -> m (a (n, p) e)Source
Create a zero banded matrix with the specified shape and bandwidths.
setZeroBanded :: WriteBanded a e m => a (n, p) e -> m ()Source
Set every element of a banded matrix to zero.
newConstantBanded :: WriteBanded a e m => (Int, Int) -> (Int, Int) -> e -> m (a (n, p) e)Source
Create a constant banded matrix of the specified shape and bandwidths.
setConstantBanded :: WriteBanded a e m => e -> a (n, p) e -> m ()Source
Set every element of a banded matrix to a constant.
Copying banded matrices
newCopyBanded :: (ReadBanded a e m, WriteBanded b e m) => a (n, p) e -> m (b (n, p) e)Source
Create a new banded matrix by taking a copy of another one.
copyBanded :: (WriteBanded b e m, ReadBanded a e m) => b (n, p) e -> a (n, p) e -> m ()Source
Copy the elements of one banded matrix into another. The two matrices must have the same shape and badwidths.
Conversions between banded matrices and vectors
Row and column views
rowViewBanded :: BaseBanded a e => a (n, p) e -> Int -> (Int, VectorView a k e, Int)Source
Get a view into the partial row of the banded matrix, along with the number of zeros to pad before and after the view.
colViewBanded :: BaseBanded a e => a (n, p) e -> Int -> (Int, VectorView a k e, Int)Source
Get a view into the partial column of the banded matrix, along with the number of zeros to pad before and after the view.
diagViewBanded :: BaseBanded a e => a (n, p) e -> Int -> VectorView a k eSource
Get a view of a diagonal of the banded matrix. This will fail if the index is outside of the bandwidth.
Getting diagonals
getDiagBanded :: (ReadBanded a e m, WriteVector y e m) => a (n, p) e -> Int -> m (y k e)Source
Get a copy of the given diagonal of a banded matrix.
Overloaded interface for reading and writing banded matrix elements
module Data.Tensor.Class
module Data.Tensor.Class.MTensor