Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
Numeric.BLAS.Matrix.RowMajor
Synopsis
- type Matrix height width = Array (height, width)
- type Square sh = Matrix sh sh
- type Vector = Array
- height :: Matrix height width a -> height
- width :: Matrix height width a -> width
- singleRow :: Array width a -> Array2 () width a
- flattenRow :: Array2 () width a -> Array width a
- singleColumn :: Array height a -> Array2 height () a
- flattenColumn :: Array2 height () a -> Array height a
- identity :: (C sh, Floating a) => sh -> Square sh a
- takeRow :: (Indexed height, C width, Index height ~ ix, Storable a) => ix -> Matrix height width a -> Vector width a
- takeColumn :: (C height, Indexed width, Index width ~ ix, Floating a) => ix -> Matrix height width a -> Vector height a
- fromRows :: (C width, Eq width, Storable a) => width -> [Vector width a] -> Matrix ShapeInt width a
- above :: (C heightA, C heightB) => (C width, Eq width) => Storable a => Matrix heightA width a -> Matrix heightB width a -> Matrix (heightA ::+ heightB) width a
- beside :: (C widthA, C widthB) => (C height, Eq height) => Storable a => Matrix height widthA a -> Matrix height widthB a -> Matrix height (widthA ::+ widthB) a
- takeTop :: (C heightA, C heightB, C width, Storable a) => Matrix (heightA ::+ heightB) width a -> Matrix heightA width a
- takeBottom :: (C heightA, C heightB, C width, Storable a) => Matrix (heightA ::+ heightB) width a -> Matrix heightB width a
- takeLeft :: (C height, C widthA, C widthB, Storable a) => Matrix height (widthA ::+ widthB) a -> Matrix height widthA a
- takeRight :: (C height, C widthA, C widthB, Storable a) => Matrix height (widthA ::+ widthB) a -> Matrix height widthB a
- tensorProduct :: (C height, C width, Floating a) => Either Conjugation Conjugation -> Vector height a -> Vector width a -> Matrix height width a
- decomplex :: Real a => Matrix height width (Complex a) -> Matrix height (width, ComplexShape) a
- recomplex :: Real a => Matrix height (width, ComplexShape) a -> Matrix height width (Complex a)
- scaleRows :: (C height, Eq height, C width, Floating a) => Vector height a -> Matrix height width a -> Matrix height width a
- scaleColumns :: (C height, C width, Eq width, Floating a) => Vector width a -> Matrix height width a -> Matrix height width a
- multiplyVectorLeft :: (Eq height, C height, C width, Floating a) => Vector height a -> Matrix height width a -> Vector width a
- multiplyVectorRight :: (C height, C width, Eq width, Floating a) => Matrix height width a -> Vector width a -> Vector height a
- data Transposable height width a
- = NonTransposed (Matrix height width a)
- | Transposed (Matrix width height a)
- nonTransposed :: Matrix height width a -> Transposable height width a
- transposed :: Matrix height width a -> Transposable width height a
- transposeTransposable :: Transposable height width a -> Transposable width height a
- multiply :: (C height, C width, C fuse, Eq fuse, Floating a) => Matrix height fuse a -> Matrix fuse width a -> Matrix height width a
- multiplyTransposable :: (C height, C width, C fuse, Eq fuse, Floating a) => Transposable height fuse a -> Transposable fuse width a -> Matrix height width a
- kronecker :: (C heightA, C widthA, C heightB, C widthB, Floating a) => Matrix heightA widthA a -> Matrix heightB widthB a -> Matrix (heightA, heightB) (widthA, widthB) a
- kroneckerTransposable :: (C heightA, C widthA, C heightB, C widthB, Floating a) => Transposable heightA widthA a -> Transposable heightB widthB a -> Transposable (heightA, heightB) (widthA, widthB) a
- kroneckerLeftTransposable :: (C heightA, C widthA, C heightB, C widthB, Floating a) => Transposable heightA widthA a -> Matrix heightB widthB a -> Matrix (heightA, heightB) (widthA, widthB) a
Documentation
type Square sh = Matrix sh sh Source #
There is also Square
but this would be incompatible with other matrix operations.
This might be addressed in a new Matrix.Square module.
But for advanced type hacks you can already use the lapack
package.
flattenRow :: Array2 () width a -> Array width a #
singleColumn :: Array height a -> Array2 height () a #
flattenColumn :: Array2 height () a -> Array height a #
identity :: (C sh, Floating a) => sh -> Square sh a Source #
>>>
Matrix.identity (Shape.ZeroBased 0) :: Matrix.Square (Shape.ZeroBased Int) Real_
StorableArray.fromList (ZeroBased {... 0},ZeroBased {... 0}) []>>>
Matrix.identity (Shape.ZeroBased 3) :: Matrix.Square (Shape.ZeroBased Int) Real_
StorableArray.fromList (ZeroBased {... 3},ZeroBased {... 3}) [1.0,0.0,0.0,0.0,1.0,0.0,0.0,0.0,1.0]
takeRow :: (Indexed height, C width, Index height ~ ix, Storable a) => ix -> Matrix height width a -> Vector width a Source #
takeColumn :: (C height, Indexed width, Index width ~ ix, Floating a) => ix -> Matrix height width a -> Vector height a Source #
fromRows :: (C width, Eq width, Storable a) => width -> [Vector width a] -> Matrix ShapeInt width a Source #
above :: (C heightA, C heightB) => (C width, Eq width) => Storable a => Matrix heightA width a -> Matrix heightB width a -> Matrix (heightA ::+ heightB) width a infixr 2 Source #
beside :: (C widthA, C widthB) => (C height, Eq height) => Storable a => Matrix height widthA a -> Matrix height widthB a -> Matrix height (widthA ::+ widthB) a infixr 3 Source #
takeTop :: (C heightA, C heightB, C width, Storable a) => Matrix (heightA ::+ heightB) width a -> Matrix heightA width a Source #
takeBottom :: (C heightA, C heightB, C width, Storable a) => Matrix (heightA ::+ heightB) width a -> Matrix heightB width a Source #
takeLeft :: (C height, C widthA, C widthB, Storable a) => Matrix height (widthA ::+ widthB) a -> Matrix height widthA a Source #
takeRight :: (C height, C widthA, C widthB, Storable a) => Matrix height (widthA ::+ widthB) a -> Matrix height widthB a Source #
tensorProduct :: (C height, C width, Floating a) => Either Conjugation Conjugation -> Vector height a -> Vector width a -> Matrix height width a Source #
Warning: Don't use conjugation. Left and Right are swapped.
decomplex :: Real a => Matrix height width (Complex a) -> Matrix height (width, ComplexShape) a Source #
recomplex :: Real a => Matrix height (width, ComplexShape) a -> Matrix height width (Complex a) Source #
scaleRows :: (C height, Eq height, C width, Floating a) => Vector height a -> Matrix height width a -> Matrix height width a Source #
scaleColumns :: (C height, C width, Eq width, Floating a) => Vector width a -> Matrix height width a -> Matrix height width a Source #
multiplyVectorLeft :: (Eq height, C height, C width, Floating a) => Vector height a -> Matrix height width a -> Vector width a Source #
>>>
Matrix.multiplyVectorLeft (Array.vectorFromList [3,1,4]) (Array.fromList (Shape.ZeroBased (3::Int), Shape.Range 'a' 'b') [0,1,0,0,1,0::Real_])
StorableArray.fromList (Range {rangeFrom = 'a', rangeTo = 'b'}) [4.0,3.0]
forVector number_ $ \xs -> Matrix.multiplyVectorLeft xs (Matrix.identity (Array.shape xs)) == xs
multiplyVectorRight :: (C height, C width, Eq width, Floating a) => Matrix height width a -> Vector width a -> Vector height a Source #
>>>
Matrix.multiplyVectorRight (Array.fromList (Shape.Range 'a' 'b', Shape.ZeroBased (3::Int)) [0,0,1,1,0,0]) (Array.vectorFromList [3,1,4::Real_])
StorableArray.fromList (Range {rangeFrom = 'a', rangeTo = 'b'}) [4.0,3.0]>>>
Matrix.multiplyVectorRight (Array.fromList (Shape.Range 'a' 'b', Shape.ZeroBased (3::Int)) [2,7,1,8,2,8]) (Array.vectorFromList [3,1,4::Real_])
StorableArray.fromList (Range {rangeFrom = 'a', rangeTo = 'b'}) [17.0,58.0]
forVector number_ $ \xs -> Matrix.multiplyVectorRight (Matrix.identity (Array.shape xs)) xs == xs
forMatrix number_ $ \a -> QC.forAll (genVector (snd $ Array.shape a) number_) $ \x -> Matrix.singleColumn (Matrix.multiplyVectorRight a x) == Matrix.multiply a (Matrix.singleColumn x)
forMatrix number_ $ \a -> QC.forAll (genVector (fst $ Array.shape a) number_) $ \x -> QC.forAll (genVector (snd $ Array.shape a) number_) $ \y -> Vector.dot x (Matrix.multiplyVectorRight a y) == Vector.dot (Matrix.multiplyVectorLeft x a) y
forMatrix number_ $ \a -> QC.forAll (genVector (snd $ Array.shape a) number_) $ \x -> Matrix.multiplyVectorRight a x == Matrix.multiplyVectorLeft x (transpose a)
data Transposable height width a Source #
Constructors
NonTransposed (Matrix height width a) | |
Transposed (Matrix width height a) |
Instances
(C height, C width, Storable a, Show height, Show width, Show a) => Show (Transposable height width a) Source # | |
Defined in Numeric.BLAS.Matrix.RowMajor Methods showsPrec :: Int -> Transposable height width a -> ShowS # show :: Transposable height width a -> String # showList :: [Transposable height width a] -> ShowS # |
nonTransposed :: Matrix height width a -> Transposable height width a Source #
transposed :: Matrix height width a -> Transposable width height a Source #
transposeTransposable :: Transposable height width a -> Transposable width height a Source #
multiply :: (C height, C width, C fuse, Eq fuse, Floating a) => Matrix height fuse a -> Matrix fuse width a -> Matrix height width a Source #
>>>
Matrix.multiply (Array.fromList (shapeInt 2, shapeInt 2) [1000,100,10,1]) (Array.fromList (shapeInt 2, shapeInt 3) [0..5::Real_])
... [300.0,1400.0,2500.0,3.0,14.0,25.0]
forMatrix number_ $ \a -> Matrix.multiply (Matrix.identity (Matrix.height a)) a == a
forMatrix number_ $ \a -> Matrix.multiply a (Matrix.identity (Matrix.width a)) == a
forMatrix number_ $ \a -> forMatrix number_ $ \c -> QC.forAll (genVector (Matrix.width a, Matrix.height c) number_) $ \b -> Matrix.multiply a (Matrix.multiply b c) == Matrix.multiply (Matrix.multiply a b) c
multiplyTransposable :: (C height, C width, C fuse, Eq fuse, Floating a) => Transposable height fuse a -> Transposable fuse width a -> Matrix height width a Source #
forMatrix number_ $ \a -> QC.forAll (genIdentityTrans (Matrix.height a)) $ \eye -> a == Matrix.multiplyTransposable eye (Matrix.nonTransposed a)
forMatrix number_ $ \a -> QC.forAll (genIdentityTrans (Matrix.width a)) $ \eye -> a == Matrix.multiplyTransposable (Matrix.nonTransposed a) eye
forMatrix number_ $ \a -> QC.forAll (genIdentityTrans (Matrix.width a)) $ \leftEye -> QC.forAll (genIdentityTrans (Matrix.height a)) $ \rightEye -> Matrix.multiplyTransposable leftEye (Matrix.transposed a) == Matrix.multiplyTransposable (Matrix.transposed a) rightEye
forMatrix number_ $ \a -> QC.forAll (QC.choose (0,maxDim)) $ \n -> QC.forAll (genVector (Matrix.width a, shapeInt n) number_) $ \b -> transpose (Matrix.multiply a b) == Matrix.multiplyTransposable (Matrix.transposed b) (Matrix.transposed a)
kronecker :: (C heightA, C widthA, C heightB, C widthB, Floating a) => Matrix heightA widthA a -> Matrix heightB widthB a -> Matrix (heightA, heightB) (widthA, widthB) a Source #
>>>
Matrix.kronecker (Array.fromList (shapeInt 2, shapeInt 2) [0,1,-1,0::Real_]) (Array.fromList (shapeInt 2, shapeInt 3) [1..6])
... [0.0,0.0,0.0,1.0,2.0,3.0,0.0,0.0,0.0,4.0,5.0,6.0,-1.0,-2.0,-3.0,0.0,0.0,0.0,-4.0,-5.0,-6.0,0.0,0.0,0.0]
>>>
Matrix.kronecker (Array.fromList (shapeInt 2, shapeInt 2) [1,2,3,4::Real_]) (Array.fromList (shapeInt 2, shapeInt 3) [1,2,4,8,16,32])
... [1.0,2.0,4.0,2.0,4.0,8.0,8.0,16.0,32.0,16.0,32.0,64.0,3.0,6.0,12.0,4.0,8.0,16.0,24.0,48.0,96.0,32.0,64.0,128.0]
QC.forAll (QC.choose (0,5)) $ \m -> QC.forAll (QC.choose (0,5)) $ \n -> Matrix.kronecker (Matrix.identity (shapeInt m)) (Matrix.identity (shapeInt n)) == (Matrix.identity (shapeInt m, shapeInt n) :: Matrix.Square (ShapeInt, ShapeInt) Number_)
kroneckerTransposable :: (C heightA, C widthA, C heightB, C widthB, Floating a) => Transposable heightA widthA a -> Transposable heightB widthB a -> Transposable (heightA, heightB) (widthA, widthB) a Source #