Safe Haskell | None |
---|---|
Language | Haskell2010 |
Data.Vector.Fixed.Unboxed
Description
Adaptive array type which picks vector representation from type of
element of array. For example arrays of Double
are backed by
ByteArray
, arrays of Bool
are represented as bit-vector, arrays
of tuples are products of arrays. Unbox
type class is used to
describe representation of an array.
Synopsis
- newtype Vec (n :: Nat) a = Vec {
- getVecRepr :: VecRepr n a (EltRepr a)
- type Vec1 = Vec 1
- type Vec2 = Vec 2
- type Vec3 = Vec 3
- type Vec4 = Vec 4
- type Vec5 = Vec 5
- class (Dim (VecRepr n a) ~ Peano n, Vector (VecRepr n a) (EltRepr a)) => Unbox (n :: Nat) a
- data UnboxViaPrim a
- data BitVec (n :: Nat) a
- data T2 (n :: Nat) a b x = T2 !(Vec n a) !(Vec n b)
- data T3 (n :: Nat) a b c x = T3 !(Vec n a) !(Vec n b) !(Vec n c)
Data type
newtype Vec (n :: Nat) a Source #
Adaptive array of dimension n
and containing elements of type
a
.
Constructors
Vec | |
Fields
|
Instances
(Arity n, Unbox n a) => Vector (Vec n) a Source # | |
(Typeable n, Unbox n a, Data a) => Data (Vec n a) Source # | |
Defined in Data.Vector.Fixed.Unboxed Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Vec n a -> c (Vec n a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Vec n a) # toConstr :: Vec n a -> Constr # dataTypeOf :: Vec n a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Vec n a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Vec n a)) # gmapT :: (forall b. Data b => b -> b) -> Vec n a -> Vec n a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Vec n a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Vec n a -> r # gmapQ :: (forall d. Data d => d -> u) -> Vec n a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Vec n a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Vec n a -> m (Vec n a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Vec n a -> m (Vec n a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Vec n a -> m (Vec n a) # | |
(Unbox n a, Storable a) => Storable (Vec n a) Source # | |
(Unbox n a, Monoid a) => Monoid (Vec n a) Source # | |
(Unbox n a, Semigroup a) => Semigroup (Vec n a) Source # | |
(Unbox n a, Show a) => Show (Vec n a) Source # | |
(Unbox n a, NFData a) => NFData (Vec n a) Source # | |
Defined in Data.Vector.Fixed.Unboxed | |
(Unbox n a, Eq a) => Eq (Vec n a) Source # | |
(Unbox n a, Ord a) => Ord (Vec n a) Source # | |
Defined in Data.Vector.Fixed.Unboxed | |
type Dim (Vec n) Source # | |
Defined in Data.Vector.Fixed.Unboxed |
Type classes & derivation
class (Dim (VecRepr n a) ~ Peano n, Vector (VecRepr n a) (EltRepr a)) => Unbox (n :: Nat) a Source #
Type class which selects internal representation of unboxed vector.
Crucial design constraint is this type class must be
GND-derivable. And this rules out anything mentioning Fun
,
since all it's parameters has nominal
role. Thus Vector
is
not GND-derivable and we have to take somewhat roundabout
approach.
Minimal complete definition
toEltRepr, fromEltRepr
Instances
data UnboxViaPrim a Source #
Wrapper for deriving Unbox
for data types which are instances
of Prim
type class:
deriving via UnboxViaPrim Word instance (C.Arity n) => Unbox n Word
Instances
Concrete representations
data BitVec (n :: Nat) a Source #
Bit vector represented as 64-bit word. This puts upper limit on length of vector. It's not a big problem. 64-element will strain GHC quite a bit.
data T2 (n :: Nat) a b x Source #
Representation for vector of 2-tuple as two vectors.