blas-0.4.1: Bindings to the BLAS librarySource codeContentsIndex
Data.Matrix.Dense.IO
Stabilityexperimental
MaintainerPatrick Perry <patperry@stanford.edu>
Contents
The mutable dense matrix data type
Creating new matrices
Special matrices
Views
Rows and columns
Diagonals
Matrix views
Operations
Lifting scalar and vector operations
Converting to and from matrices
Vectors
ForeignPtrs
Coercing
Unsafe operations
Description
This modules defines a mutable dense matrix and associate operations.
Synopsis
data DMatrix t mn e
= DM {
fptr :: !(ForeignPtr e)
offset :: !Int
size1 :: !Int
size2 :: !Int
lda :: !Int
}
| H !(DMatrix t mn e)
type IOMatrix = DMatrix Mut
module BLAS.Matrix.Base
module BLAS.Matrix.ReadOnly
module BLAS.Tensor.Base
module BLAS.Tensor.Dense.ReadOnly
module BLAS.Tensor.ReadOnly
module BLAS.Tensor.Mutable
newMatrix :: BLAS1 e => (Int, Int) -> [((Int, Int), e)] -> IO (DMatrix t (m, n) e)
newMatrix_ :: Elem e => (Int, Int) -> IO (DMatrix t (m, n) e)
newListMatrix :: Elem e => (Int, Int) -> [e] -> IO (DMatrix t (m, n) e)
newColsMatrix :: BLAS1 e => (Int, Int) -> [DVector t m e] -> IO (DMatrix r (m, n) e)
newRowsMatrix :: BLAS1 e => (Int, Int) -> [DVector t n e] -> IO (DMatrix r (m, n) e)
newIdentity :: BLAS1 e => (Int, Int) -> IO (DMatrix t (m, n) e)
setIdentity :: BLAS1 e => IOMatrix (m, n) e -> IO ()
row :: Elem e => DMatrix t (m, n) e -> Int -> DVector t n e
col :: Elem e => DMatrix t (m, n) e -> Int -> DVector t m e
rows :: Elem e => DMatrix t (m, n) e -> [DVector t n e]
cols :: Elem e => DMatrix t (m, n) e -> [DVector t m e]
diag :: Elem e => DMatrix t (m, n) e -> Int -> DVector t k e
submatrix :: Elem e => DMatrix t (m, n) e -> (Int, Int) -> (Int, Int) -> DMatrix t (k, l) e
module Data.Matrix.Dense.Operations
liftV :: Elem e => (DVector t k e -> IO ()) -> DMatrix t (m, n) e -> IO ()
liftV2 :: Elem e => (DVector s k e -> DVector t k e -> IO ()) -> DMatrix s (m, n) e -> DMatrix t (m, n) e -> IO ()
maybeFromRow :: Elem e => DVector t m e -> Maybe (DMatrix t (one, m) e)
maybeFromCol :: Elem e => DVector t n e -> Maybe (DMatrix t (n, one) e)
maybeToVector :: Elem e => DMatrix t (m, n) e -> Maybe (Order, DVector t k e)
toForeignPtr :: DMatrix t (m, n) e -> (ForeignPtr e, Int, (Int, Int), Int)
fromForeignPtr :: ForeignPtr e -> Int -> (Int, Int) -> Int -> DMatrix t (m, n) e
ldaOf :: DMatrix t (m, n) e -> Int
isHerm :: DMatrix t (m, n) e -> Bool
coerceMatrix :: DMatrix t mn e -> DMatrix t kl e
unsafeNewMatrix :: BLAS1 e => (Int, Int) -> [((Int, Int), e)] -> IO (DMatrix t (m, n) e)
unsafeWithElemPtr :: Elem e => DMatrix t (m, n) e -> (Int, Int) -> (Ptr e -> IO a) -> IO a
unsafeRow :: Elem e => DMatrix t (m, n) e -> Int -> DVector t n e
unsafeCol :: Elem e => DMatrix t (m, n) e -> Int -> DVector t m e
unsafeDiag :: Elem e => DMatrix t (m, n) e -> Int -> DVector t k e
unsafeSubmatrix :: Elem e => DMatrix t (m, n) e -> (Int, Int) -> (Int, Int) -> DMatrix t (k, l) e
unsafeFreeze :: DMatrix t mn e -> Matrix mn e
unsafeThaw :: DMatrix t mn e -> IOMatrix mn e
The mutable dense matrix data type
data DMatrix t mn e Source
The mutable dense matrix data type. It can either store elements in column-major order, or provide a view into another matrix. The view transposes and conjugates the underlying matrix.
Constructors
DM
fptr :: !(ForeignPtr e)a pointer to the storage region
offset :: !Intan offset (in elements, not bytes) to the first element in the matrix.
size1 :: !Intthe number of rows in the matrix
size2 :: !Intthe number of columns in the matrix
lda :: !Intthe leading dimension size of the matrix
H !(DMatrix t mn e)a transposed and conjugated matrix
show/hide Instances
Matrix (DMatrix t)
BLAS3 e => IMatrix (DMatrix Imm) e
BLAS3 e => RMatrix (DMatrix t) e
BLAS1 e => Scalable (DMatrix Imm ((,) m n)) e
Tensor (DMatrix t ((,) m n)) ((,) Int Int) e
BLAS1 e => ITensor (DMatrix Imm ((,) m n)) ((,) Int Int) e
BLAS1 e => IDTensor (DMatrix Imm ((,) m n)) ((,) Int Int) e
BLAS1 e => RTensor (DMatrix t ((,) m n)) ((,) Int Int) e IO
BLAS1 e => RDTensor (DMatrix t ((,) m n)) ((,) Int Int) e IO
BLAS1 e => MTensor (DMatrix Mut ((,) m n)) ((,) Int Int) e IO
(BLAS1 e, Eq e) => Eq (DMatrix Imm ((,) m n) e)
(BLAS2 e, Floating e) => Floating (DMatrix Imm ((,) m n) e)
BLAS2 e => Fractional (DMatrix Imm ((,) m n) e)
BLAS2 e => Num (DMatrix Imm ((,) m n) e)
(BLAS1 e, Show e) => Show (DMatrix Imm ((,) m n) e)
(BLAS1 e, AEq e) => AEq (DMatrix Imm ((,) m n) e)
type IOMatrix = DMatrix MutSource
module BLAS.Matrix.Base
module BLAS.Matrix.ReadOnly
module BLAS.Tensor.Base
module BLAS.Tensor.Dense.ReadOnly
module BLAS.Tensor.ReadOnly
module BLAS.Tensor.Mutable
Creating new matrices
newMatrix :: BLAS1 e => (Int, Int) -> [((Int, Int), e)] -> IO (DMatrix t (m, n) e)Source
Create a new matrix of the given size and initialize the given elements to the given values. All other elements get initialized to zero.
newMatrix_ :: Elem e => (Int, Int) -> IO (DMatrix t (m, n) e)Source
Create a new matrix of given shape, but do not initialize the elements.
newListMatrix :: Elem e => (Int, Int) -> [e] -> IO (DMatrix t (m, n) e)Source
Create a new matrix with the given elements in column-major order.
newColsMatrix :: BLAS1 e => (Int, Int) -> [DVector t m e] -> IO (DMatrix r (m, n) e)Source
Form a matrix from a list of column vectors.
newRowsMatrix :: BLAS1 e => (Int, Int) -> [DVector t n e] -> IO (DMatrix r (m, n) e)Source
Form a matrix from a list of row vectors.
Special matrices
newIdentity :: BLAS1 e => (Int, Int) -> IO (DMatrix t (m, n) e)Source
Create a new matrix of the given shape with ones along the diagonal, and zeros everywhere else.
setIdentity :: BLAS1 e => IOMatrix (m, n) e -> IO ()Source
Set the diagonal to ones, and set everywhere else to zero.
Views
Rows and columns
row :: Elem e => DMatrix t (m, n) e -> Int -> DVector t n eSource
Get a vector view of the given row in a matrix.
col :: Elem e => DMatrix t (m, n) e -> Int -> DVector t m eSource
Get a vector view of the given column in a matrix.
rows :: Elem e => DMatrix t (m, n) e -> [DVector t n e]Source
Get a list of vector views of the rows of the matrix.
cols :: Elem e => DMatrix t (m, n) e -> [DVector t m e]Source
Get a list of vector views of the columns of the matrix.
Diagonals
diag :: Elem e => DMatrix t (m, n) e -> Int -> DVector t k eSource
diag a 0 gets a vector view of the main diagonal of a. diag a k for k positive gets a view of the kth superdiagonal. For k negative, it gets a view of the (-k)th subdiagonal.
Matrix views
submatrix :: Elem e => DMatrix t (m, n) e -> (Int, Int) -> (Int, Int) -> DMatrix t (k, l) eSource
submatrix a ij mn returns a view of the submatrix of a with element (0,0) being element ij in a, and having shape mn.
Operations
module Data.Matrix.Dense.Operations
Lifting scalar and vector operations
liftV :: Elem e => (DVector t k e -> IO ()) -> DMatrix t (m, n) e -> IO ()Source

Modify each element in-place by applying a function to it. modifyWith :: (Elem e) => (e -> e) -> IOMatrix (m,n) e -> IO ()

Take a unary elementwise vector operation and apply it to the elements of a matrix.

liftV2 :: Elem e => (DVector s k e -> DVector t k e -> IO ()) -> DMatrix s (m, n) e -> DMatrix t (m, n) e -> IO ()Source
Take a binary elementwise vector operation and apply it to the elements of a pair of matrices.
Converting to and from matrices
Vectors
maybeFromRow :: Elem e => DVector t m e -> Maybe (DMatrix t (one, m) e)Source
Create a matrix view of a row vector. This will fail if the stride is not 1 and the vector is conjugated.
maybeFromCol :: Elem e => DVector t n e -> Maybe (DMatrix t (n, one) e)Source
Possibly create a matrix view of a column vector. This will fail if the stride of the vector is not 1 and the vector is not conjugated.
maybeToVector :: Elem e => DMatrix t (m, n) e -> Maybe (Order, DVector t k e)Source
ForeignPtrs
toForeignPtr :: DMatrix t (m, n) e -> (ForeignPtr e, Int, (Int, Int), Int)Source
Convert a dense matrix to a pointer, offset, size, and lda. Note that this does not give the conjugacy/transpose information. For that, use isHerm.
fromForeignPtr :: ForeignPtr e -> Int -> (Int, Int) -> Int -> DMatrix t (m, n) eSource
fromForeignPtr f o mn l creates a matrix view of the data pointed to by f starting at offset o and having shape mn and lda l.
ldaOf :: DMatrix t (m, n) e -> IntSource
Get the lda of a matrix, defined as the number of elements in the underlying array that separate two consecutive elements in the same row of the matrix.
isHerm :: DMatrix t (m, n) e -> BoolSource
Get whether or not the matrix is transposed and conjugated.
Coercing
coerceMatrix :: DMatrix t mn e -> DMatrix t kl eSource
Coerce the phantom shape type from one type to another.
Unsafe operations
unsafeNewMatrix :: BLAS1 e => (Int, Int) -> [((Int, Int), e)] -> IO (DMatrix t (m, n) e)Source
Same as newMatrix but do not do any bounds-checking.
unsafeWithElemPtr :: Elem e => DMatrix t (m, n) e -> (Int, Int) -> (Ptr e -> IO a) -> IO aSource
Evaluate a function with a pointer to the raw storage for the element at the given index. It may be necessary to conjugate or scale values before reading or writing to or from the location.
unsafeRow :: Elem e => DMatrix t (m, n) e -> Int -> DVector t n eSource
Same as row, but does not do any bounds checking.
unsafeCol :: Elem e => DMatrix t (m, n) e -> Int -> DVector t m eSource
Same as col, but does not do any bounds checking.
unsafeDiag :: Elem e => DMatrix t (m, n) e -> Int -> DVector t k eSource
Same as diag, but does not do any bounds checking.
unsafeSubmatrix :: Elem e => DMatrix t (m, n) e -> (Int, Int) -> (Int, Int) -> DMatrix t (k, l) eSource
Same as submatrix but does not do any bounds checking.
unsafeFreeze :: DMatrix t mn e -> Matrix mn eSource
unsafeThaw :: DMatrix t mn e -> IOMatrix mn eSource
Produced by Haddock version 2.3.0