Copyright | (C) 2017 Alexey Vagarenko |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | Alexey Vagarenko (vagarenko@gmail.com) |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
- type Matrix m n e = Tensor '[m, n] e
- type MatrixConstructor m n e = TensorConstructor '[m, n] e
- type IsMatrix m n e = IsTensor '[m, n] e
- matrix :: forall m n e. IsMatrix m n e => MatrixConstructor m n e
- identity :: forall m e. (IsMatrix m m e, Generate '[m, m] e ([Nat] -> Constraint) (IdentityWrk e), Num e) => Matrix m m e
- type Identity m e = (IsMatrix m m e, Generate '[m, m] e ([Nat] -> Constraint) (IdentityWrk e), Num e)
- row :: forall (r :: Nat) (m :: Nat) (n :: Nat) e. Row r m n e => Lens' (Matrix m n e) (Vector n e)
- type Row (r :: Nat) (m :: Nat) (n :: Nat) e = (SubtensorCtx '[r] '[m, n] e, r <= (m - 1), NormalizeDims '[n] ~ '[n])
- getRowElems :: forall (r :: Nat) (m :: Nat) (n :: Nat) e. GetRowElems r m n e => Matrix m n e -> [e]
- type GetRowElems (r :: Nat) (m :: Nat) (n :: Nat) e = GetSubtensorElems '[r] '[m, n] e
- setRowElems :: forall (r :: Nat) (m :: Nat) (n :: Nat) e. SetRowElems r m n e => Matrix m n e -> [e] -> Maybe (Matrix m n e)
- type SetRowElems (r :: Nat) (m :: Nat) (n :: Nat) e = SetSubtensorElems '[r] '[m, n] e
- mapRowElems :: forall (r :: Nat) (m :: Nat) (n :: Nat) e. MapRowElems r m n e => Matrix m n e -> (e -> e) -> Matrix m n e
- type MapRowElems (r :: Nat) (m :: Nat) (n :: Nat) e = MapSubtensorElems '[r] '[m, n] e
- col :: forall (c :: Nat) (m :: Nat) (n :: Nat) e. Col c m n e => Lens' (Matrix m n e) (Vector m e)
- type Col (c :: Nat) (m :: Nat) (n :: Nat) e = (Slice '[0, c] '[m, 1] '[m, n] e, NormalizeDims '[m, 1] ~ '[m])
- getColElems :: forall (c :: Nat) (m :: Nat) (n :: Nat) e. GetColElems c m n e => Matrix m n e -> [e]
- type GetColElems (c :: Nat) (m :: Nat) (n :: Nat) e = GetSliceElems '[0, c] '[m, 1] '[m, n] e
- setColElems :: forall (c :: Nat) (m :: Nat) (n :: Nat) e. SetColElems c m n e => Matrix m n e -> [e] -> Maybe (Matrix m n e)
- type SetColElems (c :: Nat) (m :: Nat) (n :: Nat) e = SetSliceElems '[0, c] '[m, 1] '[m, n] e
- mapColElems :: forall (c :: Nat) (m :: Nat) (n :: Nat) e. MapColElems c m n e => Matrix m n e -> (e -> e) -> Matrix m n e
- type MapColElems (c :: Nat) (m :: Nat) (n :: Nat) e = MapSliceElems '[0, c] '[m, 1] '[m, n] e
- type family MatrixMultDims (dims0 :: [Nat]) (dims1 :: [Nat]) :: [Nat] where ...
- class MatrixMult (dims0 :: [Nat]) (dims1 :: [Nat]) e where
- transpose :: forall m n e. Transpose m n e => Matrix m n e -> Matrix n m e
- type Transpose m n e = (IsMatrix m n e, IsMatrix n m e, Generate '[n, m] e ([Nat] ~> Constraint) (TransposeGoSym3 m n e))
- minorMatrix :: forall (i :: Nat) (j :: Nat) (n :: Nat) e. Generate [n - 1, n - 1] e ([Nat] ~> Constraint) (MinorMatrixGoSym4 i j n e) => Matrix n n e -> Matrix (n - 1) (n - 1) e
- type MinorMatrix (i :: Nat) (j :: Nat) (n :: Nat) e = Generate [n - 1, n - 1] e ([Nat] ~> Constraint) (MinorMatrixGoSym4 i j n e)
- class Determinant (n :: Nat) e where
- minor :: forall (i :: Nat) (j :: Nat) (n :: Nat) e. Minor i j n e => Matrix n n e -> e
- type Minor (i :: Nat) (j :: Nat) (n :: Nat) e = (MinorMatrix i j n e, Determinant (n - 1) e, Num e)
- cofactor :: forall (i :: Nat) (j :: Nat) (n :: Nat) e. Cofactor i j n e => Matrix n n e -> e
- type Cofactor (i :: Nat) (j :: Nat) (n :: Nat) e = (Minor i j n e, Sign (i + j))
- cofactorMatrix :: forall (n :: Nat) e. CofactorMatrix n e => Matrix n n e -> Matrix n n e
- type CofactorMatrix (n :: Nat) e = Generate [n, n] e ([Nat] ~> Constraint) (CofactorMatrixGoSym2 n e)
- adjugateMatrix :: forall (n :: Nat) e. AdjugateMatrix n e => Matrix n n e -> Matrix n n e
- type AdjugateMatrix (n :: Nat) e = (CofactorMatrix n e, Transpose n n e)
- inverse :: forall (n :: Nat) e. Inverse n e => Matrix n n e -> Matrix n n e
- type Inverse (n :: Nat) e = (AdjugateMatrix n e, Determinant n e, Fractional e, Scale '[n, n] e)
- genMatrixInstance :: Int -> Int -> Name -> Q [Dec]
Matrix
type MatrixConstructor m n e = TensorConstructor '[m, n] e Source #
Type of matrix data constructor.
Matrix construction
matrix :: forall m n e. IsMatrix m n e => MatrixConstructor m n e Source #
Alias for a conrete matrix data constructor.
:: (IsMatrix m m e, Generate '[m, m] e ([Nat] -> Constraint) (IdentityWrk e), Num e) | |
=> Matrix m m e |
Identity matrix of size m*m
type Identity m e = (IsMatrix m m e, Generate '[m, m] e ([Nat] -> Constraint) (IdentityWrk e), Num e) Source #
Constraints for identity
function.
Matrix elements
Rows
Lens for the row number r
of the matrix m
xn
.
>>>
matrix @2 @2 @Float 0 1 2 3 ^. row @0
Tensor'2 [0.0,1.0]
>>>
set (row @1) (vector @2 @Float 20 30) (matrix @2 @2 @Float 0 1 2 3)
Tensor'2'2 [[0.0,1.0],[20.0,30.0]]
type Row (r :: Nat) (m :: Nat) (n :: Nat) e = (SubtensorCtx '[r] '[m, n] e, r <= (m - 1), NormalizeDims '[n] ~ '[n]) Source #
Constraints for row
function.
:: forall (r :: Nat) (m :: Nat) (n :: Nat). GetRowElems r m n e | |
=> Matrix m n e | |
-> [e] |
List of elements of the row number r
of the matrix m
xn
.
>>>
getRowElems @0 (matrix @2 @2 @Float 0 1 2 3)
[0.0,1.0]
type GetRowElems (r :: Nat) (m :: Nat) (n :: Nat) e = GetSubtensorElems '[r] '[m, n] e Source #
Constraints for getRowElems
function.
:: forall (r :: Nat) (m :: Nat) (n :: Nat). SetRowElems r m n e | |
=> Matrix m n e | The matrix. |
-> [e] | New row elements. |
-> Maybe (Matrix m n e) |
Put elements of the list into row number r
. The list must have enough elements.
>>>
setRowElems @1 (matrix @2 @2 @Float 0 1 2 3) [20, 30]
Just Tensor'2'2 [[0.0,1.0],[20.0,30.0]]
>>>
setRowElems @1 (matrix @2 @2 @Float 0 1 2 3) [20]
Nothing
type SetRowElems (r :: Nat) (m :: Nat) (n :: Nat) e = SetSubtensorElems '[r] '[m, n] e Source #
Constraints for setRowElems
function.
:: forall (r :: Nat) (m :: Nat) (n :: Nat). MapRowElems r m n e | |
=> Matrix m n e | The matrix. |
-> (e -> e) | The mapping function. |
-> Matrix m n e |
Apply a function to all elements of the row number r
.
>>>
mapRowElems @1 (matrix @2 @2 @Float 0 1 2 3) (* 100)
Tensor'2'2 [[0.0,1.0],[200.0,300.0]]
type MapRowElems (r :: Nat) (m :: Nat) (n :: Nat) e = MapSubtensorElems '[r] '[m, n] e Source #
Constraints for mapRowElems
function.
Columns
Lens for the column number c
of the matrix m
xn
.
>>>
matrix @2 @2 @Float 0 1 2 3 ^. col @0
Tensor'2 [0.0,2.0]
>>>
set (col @1) (vector @2 @Float 10 30) (matrix @2 @2 @Float 0 1 2 3)
Tensor'2'2 [[0.0,10.0],[2.0,30.0]]
type Col (c :: Nat) (m :: Nat) (n :: Nat) e = (Slice '[0, c] '[m, 1] '[m, n] e, NormalizeDims '[m, 1] ~ '[m]) Source #
Constraints for col
function.
:: forall (c :: Nat) (m :: Nat) (n :: Nat). GetColElems c m n e | |
=> Matrix m n e | |
-> [e] |
List of elements of the column number c
of the matrix m
xn
.
>>>
getColElems @0 (matrix @2 @2 @Float 0 1 2 3)
[0.0,2.0]
type GetColElems (c :: Nat) (m :: Nat) (n :: Nat) e = GetSliceElems '[0, c] '[m, 1] '[m, n] e Source #
Constraints for getColElems
function.
:: forall (c :: Nat) (m :: Nat) (n :: Nat). SetColElems c m n e | |
=> Matrix m n e | The matrix. |
-> [e] | New column elements. |
-> Maybe (Matrix m n e) |
Put elements of the list into column number r
. The list must have enough elements.
>>>
setColElems @1 (matrix @2 @2 @Float 0 1 2 3) [10, 30]
Just Tensor'2'2 [[0.0,10.0],[2.0,30.0]]
>>>
setColElems @1 (matrix @2 @2 @Float 0 1 2 3) [10]
Nothing
type SetColElems (c :: Nat) (m :: Nat) (n :: Nat) e = SetSliceElems '[0, c] '[m, 1] '[m, n] e Source #
Constraints for setColElems
function.
:: forall (c :: Nat) (m :: Nat) (n :: Nat). MapColElems c m n e | |
=> Matrix m n e | |
-> (e -> e) | |
-> Matrix m n e |
Apply a function to all elements of the column number c
.
>>>
mapColElems @1 (matrix @2 @2 @Float 0 1 2 3) (* 100)
Tensor'2'2 [[0.0,100.0],[2.0,300.0]]
type MapColElems (c :: Nat) (m :: Nat) (n :: Nat) e = MapSliceElems '[0, c] '[m, 1] '[m, n] e Source #
Constraints for mapColElems
function.
Matrix multiplication
type family MatrixMultDims (dims0 :: [Nat]) (dims1 :: [Nat]) :: [Nat] where ... Source #
Shape of the result of matrix multiplication.
MatrixMultDims '[m, n] '[n, o] = '[m, o] | |
MatrixMultDims '[n] '[n, o] = '[o] | |
MatrixMultDims '[m, n] '[n] = '[m] | |
MatrixMultDims a b = TypeError ((((Text "Matrices of shapes " :<>: ShowType a) :<>: Text " and ") :<>: ShowType b) :<>: Text " are incompatible for multiplication.") |
class MatrixMult (dims0 :: [Nat]) (dims1 :: [Nat]) e where Source #
Matrix multiplication.
:: (IsTensor dims0 e, IsTensor dims1 e, IsTensor (MatrixMultDims dims0 dims1) e) | |
=> Tensor dims0 e | |
-> Tensor dims1 e | |
-> Tensor (MatrixMultDims dims0 dims1) e |
Multiply two matrices, or matrix and vector. Matrices (or matrix and vector) must have compatible dimensions.
(Num e, Generate (MatrixMultDims ((:) Nat m ((:) Nat n ([] Nat))) ((:) Nat n ((:) Nat o ([] Nat)))) e ((~>) [Nat] Constraint) (MultMatMatGoSym4 m n o e)) => MatrixMult ((:) Nat m ((:) Nat n ([] Nat))) ((:) Nat n ((:) Nat o ([] Nat))) e Source # | Multiply two matrices. |
(Num e, Generate (MatrixMultDims ((:) Nat n ([] Nat)) ((:) Nat n ((:) Nat o ([] Nat)))) e ((~>) [Nat] Constraint) (MultVecMatGoSym4 m n o e)) => MatrixMult ((:) Nat n ([] Nat)) ((:) Nat n ((:) Nat o ([] Nat))) e Source # | Multiply vector and matrix. |
(Num e, Generate (MatrixMultDims ((:) Nat m ((:) Nat n ([] Nat))) ((:) Nat n ([] Nat))) e ((~>) [Nat] Constraint) (MultMatVecGoSym4 m n o e)) => MatrixMult ((:) Nat m ((:) Nat n ([] Nat))) ((:) Nat n ([] Nat)) e Source # | Multiply matrix and vector. |
Matrix operations
type Transpose m n e = (IsMatrix m n e, IsMatrix n m e, Generate '[n, m] e ([Nat] ~> Constraint) (TransposeGoSym3 m n e)) Source #
Constraints for transpose
function.
:: forall (i :: Nat) (j :: Nat) (n :: Nat). Generate [n - 1, n - 1] e ([Nat] ~> Constraint) (MinorMatrixGoSym4 i j n e) | |
=> Matrix n n e | |
-> Matrix (n - 1) (n - 1) e |
Minor matrix is a matrix made by deleting i
-th row and j
-th column from given square matrix.
type MinorMatrix (i :: Nat) (j :: Nat) (n :: Nat) e = Generate [n - 1, n - 1] e ([Nat] ~> Constraint) (MinorMatrixGoSym4 i j n e) Source #
Constraint for minorMatrix
function.
class Determinant (n :: Nat) e where Source #
Determinant of a matrix.
determinant :: Num e => Matrix n n e -> e Source #
(Num e, IsMatrix n n e, DemoteWith Nat ((~>) Nat Constraint) (DeterminantGoSym2 n e) (NatsFromTo 0 ((-) n 1)), Sum n e) => Determinant n e Source # | |
(Num e, IsMatrix 2 2 e) => Determinant 2 e Source # | |
(Num e, IsMatrix 3 3 e) => Determinant 3 e Source # | |
Minor is the determinant of minor matrix.
type Minor (i :: Nat) (j :: Nat) (n :: Nat) e = (MinorMatrix i j n e, Determinant (n - 1) e, Num e) Source #
Constraint for minor
function.
type Cofactor (i :: Nat) (j :: Nat) (n :: Nat) e = (Minor i j n e, Sign (i + j)) Source #
Constraint for cofactor
function.
:: forall (n :: Nat). CofactorMatrix n e | |
=> Matrix n n e | |
-> Matrix n n e |
The matrix formed by all of the cofactors of given square matrix.
type CofactorMatrix (n :: Nat) e = Generate [n, n] e ([Nat] ~> Constraint) (CofactorMatrixGoSym2 n e) Source #
Constraint for cofactorMatrix
function.
:: forall (n :: Nat). AdjugateMatrix n e | |
=> Matrix n n e | |
-> Matrix n n e |
Adjugate matrix of given square matrix is the transpose of its cofactor matrix.
adjugateMatrix = transpose . cofactorMatrix
type AdjugateMatrix (n :: Nat) e = (CofactorMatrix n e, Transpose n n e) Source #
Constraint for adjugateMatrix
function.
Inverse of the matrix.
type Inverse (n :: Nat) e = (AdjugateMatrix n e, Determinant n e, Fractional e, Scale '[n, n] e) Source #
Constraint for inverse
function.