|
Data.Matrix.Dense.Internal | Stability | experimental | Maintainer | Patrick Perry <patperry@stanford.edu> |
|
|
|
|
|
Description |
|
|
Synopsis |
|
| | 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) | | 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 | | 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
|
|
|
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 :: !Int | an offset (in elements, not bytes) to the first element in the matrix.
| size1 :: !Int | the number of rows in the matrix
| size2 :: !Int | the number of columns in the matrix
| lda :: !Int | the leading dimension size of the matrix
|
| H !(DMatrix t mn e) | a transposed and conjugated matrix
|
| 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) |
|
|
|
|
|
|
|
module BLAS.Matrix.Base |
|
module BLAS.Tensor |
|
Converting to and from foreign pointers
|
|
|
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 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.
|
|
|
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.
|
|
|
Get whether or not the matrix is transposed and conjugated.
|
|
Creating new matrices
|
|
|
Create a new matrix of the given size and initialize the given elements to
the given values. All other elements get initialized to zero.
|
|
|
Create a new matrix of given shape, but do not initialize the elements.
|
|
|
Create a new matrix with the given elements in column-major order.
|
|
|
Form a matrix from a list of column vectors.
|
|
|
Form a matrix from a list of row vectors.
|
|
|
Create a new matrix with the given elements in row-major order.
|
|
Special matrices
|
|
|
Create a new matrix of the given shape with ones along the diagonal,
and zeros everywhere else.
|
|
|
Set the diagonal to ones, and set everywhere else to zero.
|
|
Row and column views
|
|
|
Get a vector view of the given row in a matrix.
|
|
|
Get a vector view of the given column in a matrix.
|
|
|
Get a list of vector views of the rows of the matrix.
|
|
|
Get a list of vector views of the columns of the matrix.
|
|
Diagonal views
|
|
|
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 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
|
|
|
Create a matrix view of a row vector. This will fail if the
stride is not 1 and the vector is conjugated.
|
|
|
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.
|
|
|
|
Lifting scalar and vector operations
|
|
|
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.
|
|
|
Take a binary elementwise vector operation and apply it to the elements of a pair
of matrices.
|
|
Casting matrices
|
|
|
Coerce the phantom shape type from one type to another.
|
|
Unsafe operations
|
|
|
|
|
|
|
Same as newMatrix but do not do any bounds-checking.
|
|
|
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.
|
|
|
Same as row, but does not do any bounds checking.
|
|
|
Same as col, but does not do any bounds checking.
|
|
|
Same as diag, but does not do any bounds checking.
|
|
|
Same as submatrix but does not do any bounds checking.
|
|
Produced by Haddock version 2.3.0 |