comfort-blas-0.0.2: Numerical Basic Linear Algebra using BLAS
Safe HaskellSafe-Inferred
LanguageHaskell98

Numeric.BLAS.Slice

Synopsis

Documentation

>>> :set -XTypeOperators
>>> 
>>> import qualified Numeric.BLAS.Slice as Slice
>>> import Test.Slice (shapeInt)
>>> 
>>> import qualified Data.Array.Comfort.Boxed as Array
>>> import qualified Data.Array.Comfort.Shape as Shape
>>> import qualified Data.Map as Map
>>> import Data.Array.Comfort.Shape ((::+)((::+)))
>>> import Data.Array.Comfort.Boxed ((!))
>>> 
>>> import Control.Applicative (liftA2, liftA3, pure)
>>> 
>>> import qualified Test.QuickCheck as QC
>>> 
>>> genShape :: QC.Gen (Shape.Range Int)
>>> genShape =
>>> liftA2
>>> (\m n -> Shape.Range (min m n) (max m n))
>>> QC.arbitrary QC.arbitrary
>>> 
>>> genAppend :: QC.Gen (Shape.Range Int ::+ Shape.Range Int)
>>> genAppend = liftA2 (::+) genShape genShape
>>> 
>>> genSlice :: sh -> QC.Gen (Slice.T sh)
>>> genSlice sh =
>>> liftA3 Slice.Cons (QC.choose (0,100)) (QC.choose (1,100)) (pure sh)
>>> 
>>> genSlice2 :: shA -> shB -> QC.Gen (Slice.T shA, Slice.T shB)
>>> genSlice2 shA shB = do
>>> s <- QC.choose (0,100)
>>> k <- QC.choose (1,100)
>>> return (Slice.Cons s k shA, Slice.Cons s k shB)
>>> 
>>> type ShapeInt = Shape.ZeroBased Int
>>> 
>>> mapShape :: (shA -> shB) -> Slice.T shA -> Slice.T shB
>>> mapShape f (Slice.Cons s k sh) = Slice.Cons s k (f sh)
>>> 
>>> toShapeInt :: (Shape.C sh) => Slice.T sh -> Slice.T ShapeInt
>>> toShapeInt = mapShape (shapeInt . Shape.size)

data T sh Source #

Constructors

Cons 

Fields

Instances

Instances details
Show sh => Show (T sh) Source # 
Instance details

Defined in Numeric.BLAS.Slice

Methods

showsPrec :: Int -> T sh -> ShowS #

show :: T sh -> String #

showList :: [T sh] -> ShowS #

Eq sh => Eq (T sh) Source # 
Instance details

Defined in Numeric.BLAS.Slice

Methods

(==) :: T sh -> T sh -> Bool #

(/=) :: T sh -> T sh -> Bool #

fromShape :: C sh => sh -> T sh Source #

row :: (Indexed sh0, C sh1) => Index sh0 -> T (sh0, sh1) -> T sh1 Source #

column :: (C sh0, Indexed sh1) => Index sh1 -> T (sh0, sh1) -> T sh0 Source #

rowArray :: (Indexed sh0, C sh1) => T (sh0, sh1) -> Array sh0 (T sh1) Source #

QC.forAll (QC.choose (1,100)) $ \numRows -> QC.forAll (QC.choose (0,100)) $ \numColumns -> QC.forAll (genSlice (shapeInt numRows, shapeInt numColumns)) $ \slice -> QC.forAll (QC.elements $ Shape.indices $ shapeInt numRows) $ \ix -> Slice.row ix slice == Slice.rowArray slice ! ix

columnArray :: (C sh0, Indexed sh1) => T (sh0, sh1) -> Array sh1 (T sh0) Source #

QC.forAll (QC.choose (0,100)) $ \numRows -> QC.forAll (QC.choose (1,100)) $ \numColumns -> QC.forAll (genSlice (shapeInt numRows, shapeInt numColumns)) $ \slice -> QC.forAll (QC.elements $ Shape.indices $ shapeInt numColumns) $ \ix -> Slice.column ix slice == Slice.columnArray slice ! ix

topSubmatrix :: (C sh, C sh0, C sh1) => T (sh0 ::+ sh1, sh) -> T (sh0, sh) Source #

bottomSubmatrix :: (C sh, C sh0, C sh1) => T (sh0 ::+ sh1, sh) -> T (sh1, sh) Source #

diagonal :: C sh => T (Square sh) -> T sh Source #

cartesianFromSquare :: T (Square sh) -> T (sh, sh) Source #

squareRow :: Indexed sh => Index sh -> T (Square sh) -> T sh Source #

squareColumn :: Indexed sh => Index sh -> T (Square sh) -> T sh Source #

plane12 :: (Indexed sh0, C sh1, C sh2) => Index sh0 -> T (sh0, sh1, sh2) -> T (sh1, sh2) Source #

plane01 :: (C sh0, C sh1, Indexed sh2) => Index sh2 -> T (sh0, sh1, sh2) -> T (sh0, sh1) Source #

column2of3 :: (Indexed sh0, Indexed sh1, C sh2) => Index sh0 -> Index sh1 -> T (sh0, sh1, sh2) -> T sh2 Source #

column1of3 :: (Indexed sh0, C sh1, Indexed sh2) => Index sh0 -> Index sh2 -> T (sh0, sh1, sh2) -> T sh1 Source #

column0of3 :: (C sh0, Indexed sh1, Indexed sh2) => Index sh1 -> Index sh2 -> T (sh0, sh1, sh2) -> T sh0 Source #

left :: (C sh0, C sh1) => T (sh0 ::+ sh1) -> T sh0 Source #

right :: (C sh0, C sh1) => T (sh0 ::+ sh1) -> T sh1 Source #

take :: Int -> T ShapeInt -> T ShapeInt Source #

QC.forAll (genSlice =<< genAppend) $ \slice -> Slice.take (case Slice.shape slice of (sh::+_) -> Shape.size sh) (toShapeInt slice) == toShapeInt (Slice.left slice)

drop :: Int -> T ShapeInt -> T ShapeInt Source #

QC.forAll (genSlice =<< genAppend) $ \slice -> Slice.drop (case Slice.shape slice of (sh::+_) -> Shape.size sh) (toShapeInt slice) == toShapeInt (Slice.right slice)

sub :: Int -> Int -> T ShapeInt -> T ShapeInt Source #

Slice.sub start size
\(QC.NonNegative n) -> QC.forAll (genSlice $ shapeInt n) $ \slice (QC.NonNegative start) (QC.NonNegative size) -> Slice.sub start size slice == Slice.take size (Slice.drop start slice)

map :: C sh => T (Map k sh) -> Map k (T sh) Source #

QC.forAll (fmap shapeInt $ QC.choose (0,100)) $ \shapeA -> QC.forAll (fmap shapeInt $ QC.choose (0,100)) $ \shapeB -> QC.forAll (fmap shapeInt $ QC.choose (0,100)) $ \shapeC -> QC.forAll (genSlice2 (Map.fromList $ ('a', shapeA) : ('b', shapeB) : ('c', shapeC) : []) (shapeA ::+ shapeB ::+ shapeC)) $ \(sliceMap, sliceParted) -> Slice.map sliceMap Map.! 'b' == Slice.left (Slice.right sliceParted)
QC.forAll (QC.choose (0,100)) $ \numRows -> QC.forAll (QC.choose (0,100)) $ \numColumns -> let rowShape = shapeInt numRows; columnShape = shapeInt numColumns; mapShape_ = Map.fromList $ map (\k -> (k, columnShape)) (Shape.indices rowShape) in QC.forAll (genSlice2 mapShape_ (rowShape, columnShape)) $ \(sliceMap, sliceMatrix) -> Map.toAscList (Slice.map sliceMap) == Array.toAssociations (Slice.rowArray sliceMatrix)