Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Data.Repa.Scalar.Product
Synopsis
- data a :*: b = !a :*: !b
- class IsProdList p where
- isProdList :: p -> Bool
- class IsKeyValues p where
- class IsProdList t => Select (n :: N) t where
- class IsProdList t => Discard (n :: N) t where
- class (IsProdList m, IsProdList t) => Mask m t where
- data Keep = Keep
- data Drop = Drop
Product type
data a :*: b infixr 9 Source #
A strict product type, written infix.
Constructors
!a :*: !b infixr 9 |
Instances
IsProdList ts => Discard 'Z (t1 :*: ts) Source # | |
IsProdList ts => Select 'Z (t1 :*: ts) Source # | |
(Unbox a, Unbox b) => Vector Vector (a :*: b) Source # | |
Defined in Data.Repa.Scalar.Product Methods basicUnsafeFreeze :: Mutable Vector s (a :*: b) -> ST s (Vector (a :*: b)) basicUnsafeThaw :: Vector (a :*: b) -> ST s (Mutable Vector s (a :*: b)) basicLength :: Vector (a :*: b) -> Int basicUnsafeSlice :: Int -> Int -> Vector (a :*: b) -> Vector (a :*: b) basicUnsafeIndexM :: Vector (a :*: b) -> Int -> Box (a :*: b) basicUnsafeCopy :: Mutable Vector s (a :*: b) -> Vector (a :*: b) -> ST s () | |
(Unbox a, Unbox b) => MVector MVector (a :*: b) Source # | |
Defined in Data.Repa.Scalar.Product Methods basicLength :: MVector s (a :*: b) -> Int basicUnsafeSlice :: Int -> Int -> MVector s (a :*: b) -> MVector s (a :*: b) basicOverlaps :: MVector s (a :*: b) -> MVector s (a :*: b) -> Bool basicUnsafeNew :: Int -> ST s (MVector s (a :*: b)) basicInitialize :: MVector s (a :*: b) -> ST s () basicUnsafeReplicate :: Int -> (a :*: b) -> ST s (MVector s (a :*: b)) basicUnsafeRead :: MVector s (a :*: b) -> Int -> ST s (a :*: b) basicUnsafeWrite :: MVector s (a :*: b) -> Int -> (a :*: b) -> ST s () basicClear :: MVector s (a :*: b) -> ST s () basicSet :: MVector s (a :*: b) -> (a :*: b) -> ST s () basicUnsafeCopy :: MVector s (a :*: b) -> MVector s (a :*: b) -> ST s () basicUnsafeMove :: MVector s (a :*: b) -> MVector s (a :*: b) -> ST s () basicUnsafeGrow :: MVector s (a :*: b) -> Int -> ST s (MVector s (a :*: b)) | |
Functor ((:*:) a) Source # | |
Discard n ts => Discard ('S n) (t1 :*: ts) Source # | |
Select n ts => Select ('S n) (t1 :*: ts) Source # | |
(Show a, Show b) => Show (a :*: b) Source # | |
(Eq a, Eq b) => Eq (a :*: b) Source # | |
(IsKeyValues p, IsKeyValues ps, Keys p ~ Keys ps) => IsKeyValues (p :*: ps) Source # | |
IsProdList fs => IsProdList (f :*: fs) Source # | |
Defined in Data.Repa.Scalar.Product Methods isProdList :: (f :*: fs) -> Bool Source # | |
(Unbox a, Unbox b) => Unbox (a :*: b) Source # | |
Defined in Data.Repa.Scalar.Product | |
Mask ms ts => Mask (Drop :*: ms) (t1 :*: ts) Source # | |
Mask ms ts => Mask (Keep :*: ms) (t1 :*: ts) Source # | |
type Discard' 'Z (t1 :*: ts) Source # | |
Defined in Data.Repa.Scalar.Product | |
type Select' 'Z (t1 :*: ts) Source # | |
Defined in Data.Repa.Scalar.Product | |
data MVector s (a :*: b) Source # | |
Defined in Data.Repa.Scalar.Product | |
type Discard' ('S n) (t1 :*: ts) Source # | |
type Select' ('S n) (t1 :*: ts) Source # | |
Defined in Data.Repa.Scalar.Product | |
type Keys (p :*: ps) Source # | |
Defined in Data.Repa.Scalar.Product | |
type Values (p :*: ps) Source # | |
data Vector (a :*: b) Source # | |
Defined in Data.Repa.Scalar.Product | |
type Mask' (Drop :*: ms) (t1 :*: ts) Source # | |
type Mask' (Keep :*: ms) (t1 :*: ts) Source # | |
class IsProdList p where Source #
Sequences of products that form a valid list, using () for the nil value.
Methods
isProdList :: p -> Bool Source #
Instances
IsProdList () Source # | |
Defined in Data.Repa.Scalar.Product Methods isProdList :: () -> Bool Source # | |
IsProdList fs => IsProdList (f :*: fs) Source # | |
Defined in Data.Repa.Scalar.Product Methods isProdList :: (f :*: fs) -> Bool Source # |
class IsKeyValues p where Source #
Sequences of products and tuples that form hetrogeneous key-value pairs.
Methods
keys :: p -> [Keys p] Source #
Get a cons-list of all the keys.
values :: p -> Values p Source #
Get a heterogeneous product-list of all the values.
Instances
(IsKeyValues p, IsKeyValues ps, Keys p ~ Keys ps) => IsKeyValues (p :*: ps) Source # | |
IsKeyValues (k, v) Source # | |
Selecting
class IsProdList t => Select (n :: N) t where Source #
Methods
select :: Nat n -> t -> Select' n t Source #
Return the element with this index from a product list.
Discarding
class IsProdList t => Discard (n :: N) t where Source #
Methods
discard :: Nat n -> t -> Discard' n t Source #
Discard the element with this index from a product list.
Masking
class (IsProdList m, IsProdList t) => Mask m t where Source #
Class of data types that can have parts masked out.
Methods
mask :: m -> t -> Mask' m t Source #
Mask out some component of a type.
mask (Keep :*: Drop :*: Keep :*: ()) (1 :*: "foo" :*: 'a' :*: ()) = (1 :*: 'a' :*: ()) mask (Drop :*: Drop :*: Drop :*: ()) (1 :*: "foo" :*: 'a' :*: ()) = ()
Singleton to indicate a field that should be kept.
Constructors
Keep |