blas-0.5: Bindings to the BLAS librarySource codeContentsIndex
Data.Matrix.Dense.Internal
Stabilityexperimental
MaintainerPatrick Perry <patperry@stanford.edu>
Contents
Dense matrix data types
Converting to and from foreign pointers
Creating new matrices
Special matrices
Row and column views
Diagonal views
Matrix views
Converting to/from vectors
Lifting scalar and vector operations
Casting matrices
Unsafe operations
Description
Synopsis
data DMatrix t mn e = DM {
storageOf :: !!(ForeignPtr e)
offsetOf :: !!Int
size1 :: !!Int
size2 :: !!Int
ldaOf :: !!Int
isHerm :: !!Bool
}
type IOMatrix = DMatrix Mut
type Matrix = DMatrix Imm
module BLAS.Matrix.Base
module BLAS.Tensor
toForeignPtr :: DMatrix t (m, n) e -> (ForeignPtr e, Int, (Int, Int), Int, Bool)
fromForeignPtr :: ForeignPtr e -> Int -> (Int, Int) -> Int -> Bool -> DMatrix t (m, n) e
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)
listMatrix :: Elem e => (Int, Int) -> [e] -> Matrix (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
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)
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 ()
coerceMatrix :: DMatrix t mn e -> DMatrix t kl e
unsafeThaw :: DMatrix t mn e -> IOMatrix mn e
unsafeFreeze :: DMatrix t mn e -> Matrix mn 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
Dense matrix data types
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
storageOf :: !!(ForeignPtr e)a pointer to the storage region
offsetOf :: !!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
ldaOf :: !!Intthe leading dimension size of the matrix
isHerm :: !!Boolindicates whether or not the matrix is transposed and conjugated
show/hide Instances
Matrix (DMatrix t)
BLAS3 e => RMatrix (DMatrix t) e
BLAS3 e => IMatrix (DMatrix Imm) e
BLAS1 e => Scalable (DMatrix Imm ((,) m n)) 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
type Matrix = DMatrix ImmSource
module BLAS.Matrix.Base
module BLAS.Tensor
Converting to and from foreign pointers
toForeignPtr :: DMatrix t (m, n) e -> (ForeignPtr e, Int, (Int, Int), Int, Bool)Source
Convert a dense matrix to a pointer, offset, size, lda, herm.
fromForeignPtr :: ForeignPtr e -> Int -> (Int, Int) -> Int -> Bool -> DMatrix t (m, n) eSource
fromForeignPtr f o mn l h creates a matrix view of the data pointed to by f starting at offset o and having shape mn and lda l. If h is True the matrix is interpreted as transposed and conjugated.
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.
listMatrix :: Elem e => (Int, Int) -> [e] -> Matrix (m, n) eSource
Create a new matrix with the given elements in row-major order.
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.
Row and column views
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.
Diagonal views
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.
Converting to/from 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 vector is conjugated and the stride is not 1.
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
Lifting scalar and vector operations
liftV :: Elem e => (DVector t k e -> IO ()) -> DMatrix t (m, n) e -> IO ()Source
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.
Casting matrices
coerceMatrix :: DMatrix t mn e -> DMatrix t kl eSource
Coerce the phantom shape type from one type to another.
Unsafe operations
unsafeThaw :: DMatrix t mn e -> IOMatrix mn eSource
unsafeFreeze :: DMatrix t mn e -> Matrix mn eSource
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.
Produced by Haddock version 2.3.0