Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data MVector s a
- type IOVector = MVector RealWorld
- type STVector s = MVector s
- class Unbox (Rep a) => Unboxable a where
- type Rep a
- newtype Generics a = Generics a
- newtype Enum a = Enum a
- newtype EnumRep rep a = EnumRep a
- length :: Unboxable a => MVector s a -> Int
- null :: Unboxable a => MVector s a -> Bool
- slice :: Unboxable a => Int -> Int -> MVector s a -> MVector s a
- init :: Unboxable a => MVector s a -> MVector s a
- tail :: Unboxable a => MVector s a -> MVector s a
- take :: Unboxable a => Int -> MVector s a -> MVector s a
- drop :: Unboxable a => Int -> MVector s a -> MVector s a
- splitAt :: Unboxable a => Int -> MVector s a -> (MVector s a, MVector s a)
- unsafeSlice :: Unboxable a => Int -> Int -> MVector s a -> MVector s a
- unsafeInit :: Unboxable a => MVector s a -> MVector s a
- unsafeTail :: Unboxable a => MVector s a -> MVector s a
- unsafeTake :: Unboxable a => Int -> MVector s a -> MVector s a
- unsafeDrop :: Unboxable a => Int -> MVector s a -> MVector s a
- overlaps :: Unboxable a => MVector s a -> MVector s a -> Bool
- new :: (PrimMonad m, Unboxable a) => Int -> m (MVector (PrimState m) a)
- unsafeNew :: (PrimMonad m, Unboxable a) => Int -> m (MVector (PrimState m) a)
- replicate :: (PrimMonad m, Unboxable a) => Int -> a -> m (MVector (PrimState m) a)
- replicateM :: (PrimMonad m, Unboxable a) => Int -> m a -> m (MVector (PrimState m) a)
- clone :: (PrimMonad m, Unboxable a) => MVector (PrimState m) a -> m (MVector (PrimState m) a)
- grow :: (PrimMonad m, Unboxable a) => MVector (PrimState m) a -> Int -> m (MVector (PrimState m) a)
- unsafeGrow :: (PrimMonad m, Unboxable a) => MVector (PrimState m) a -> Int -> m (MVector (PrimState m) a)
- clear :: (PrimMonad m, Unboxable a) => MVector (PrimState m) a -> m ()
- zip :: (Unboxable a, Unboxable b) => MVector s a -> MVector s b -> MVector s (a, b)
- zip3 :: (Unboxable a, Unboxable b, Unboxable c) => MVector s a -> MVector s b -> MVector s c -> MVector s (a, b, c)
- zip4 :: (Unboxable a, Unboxable b, Unboxable c, Unboxable d) => MVector s a -> MVector s b -> MVector s c -> MVector s d -> MVector s (a, b, c, d)
- zip5 :: (Unboxable a, Unboxable b, Unboxable c, Unboxable d, Unboxable e) => MVector s a -> MVector s b -> MVector s c -> MVector s d -> MVector s e -> MVector s (a, b, c, d, e)
- zip6 :: (Unboxable a, Unboxable b, Unboxable c, Unboxable d, Unboxable e, Unboxable f) => MVector s a -> MVector s b -> MVector s c -> MVector s d -> MVector s e -> MVector s f -> MVector s (a, b, c, d, e, f)
- unzip :: (Unboxable a, Unboxable b) => MVector s (a, b) -> (MVector s a, MVector s b)
- unzip3 :: (Unboxable a, Unboxable b, Unboxable c) => MVector s (a, b, c) -> (MVector s a, MVector s b, MVector s c)
- unzip4 :: (Unboxable a, Unboxable b, Unboxable c, Unboxable d) => MVector s (a, b, c, d) -> (MVector s a, MVector s b, MVector s c, MVector s d)
- unzip5 :: (Unboxable a, Unboxable b, Unboxable c, Unboxable d, Unboxable e) => MVector s (a, b, c, d, e) -> (MVector s a, MVector s b, MVector s c, MVector s d, MVector s e)
- unzip6 :: (Unboxable a, Unboxable b, Unboxable c, Unboxable d, Unboxable e, Unboxable f) => MVector s (a, b, c, d, e, f) -> (MVector s a, MVector s b, MVector s c, MVector s d, MVector s e, MVector s f)
- read :: (PrimMonad m, Unboxable a) => MVector (PrimState m) a -> Int -> m a
- write :: (PrimMonad m, Unboxable a) => MVector (PrimState m) a -> Int -> a -> m ()
- modify :: (PrimMonad m, Unboxable a) => MVector (PrimState m) a -> (a -> a) -> Int -> m ()
- swap :: (PrimMonad m, Unboxable a) => MVector (PrimState m) a -> Int -> Int -> m ()
- unsafeRead :: (PrimMonad m, Unboxable a) => MVector (PrimState m) a -> Int -> m a
- unsafeWrite :: (PrimMonad m, Unboxable a) => MVector (PrimState m) a -> Int -> a -> m ()
- unsafeModify :: (PrimMonad m, Unboxable a) => MVector (PrimState m) a -> (a -> a) -> Int -> m ()
- unsafeSwap :: (PrimMonad m, Unboxable a) => MVector (PrimState m) a -> Int -> Int -> m ()
- nextPermutation :: (PrimMonad m, Ord e, Unboxable e) => MVector (PrimState m) e -> m Bool
- set :: (PrimMonad m, Unboxable a) => MVector (PrimState m) a -> a -> m ()
- copy :: (PrimMonad m, Unboxable a) => MVector (PrimState m) a -> MVector (PrimState m) a -> m ()
- move :: (PrimMonad m, Unboxable a) => MVector (PrimState m) a -> MVector (PrimState m) a -> m ()
- unsafeCopy :: (PrimMonad m, Unboxable a) => MVector (PrimState m) a -> MVector (PrimState m) a -> m ()
- unsafeMove :: (PrimMonad m, Unboxable a) => MVector (PrimState m) a -> MVector (PrimState m) a -> m ()
- coerceMVector :: (Coercible a b, Unboxable a, Unboxable b, CoercibleRep a ~ CoercibleRep b, Rep a ~ Rep b) => MVector s a -> MVector s b
- liftCoercionM :: (Unboxable a, Unboxable b, CoercibleRep a ~ CoercibleRep b, Rep a ~ Rep b) => Coercion a b -> Coercion (MVector s a) (MVector s b)
- mVectorCoercion :: (Coercible a b, Unboxable a, Unboxable b, CoercibleRep a ~ CoercibleRep b, Rep a ~ Rep b) => Coercion (MVector s a) (MVector s b)
- toUnboxedMVector :: (Unboxable a, Rep a ~ a, IsTrivial a ~ True) => MVector s a -> MVector s a
- fromUnboxedMVector :: (Unboxable a, Rep a ~ a, IsTrivial a ~ True) => MVector s a -> MVector s a
- coercionWithUnboxedMVector :: (Unboxable a, Rep a ~ a, IsTrivial a ~ True) => Coercion (MVector s a) (MVector s a)
Documentation
Instances
class Unbox (Rep a) => Unboxable a Source #
Types that can be stored in unboxed vectors (Vector
and MVector
).
You can define instances of this class like:
newtype Foo = Foo Int instance Unboxable Foo where type Rep Foo = Int
The type specified by Rep
needs to be an instance of Unbox
,
and coercion must be possible between the two types.
Instances can also be derived with GeneralizedNewtypeDeriving
.
GND always works if the base type is an instance of Unboxable
.
If you want to have non-trivial correspondence between the type and the representation,
use Generics
wrapper with DerivingVia
.
Note that UndecidableInstances
is needed if you use GND or DerivingVia
to derive instances.
Instances
A newtype wrapper to be used with DerivingVia
.
Usage:
data Bar = Bar !Int !Int deriving Generic deriving Unboxable via Generics Bar
Generics a |
A newtype wrapper to be used with DerivingVia
.
The value will be stored as Int
, via fromEnum
/toEnum
.
Usage:
data Direction = North | South | East | West deriving Enum deriving Data.Vector.Unboxing.Unboxable via Data.Vector.Unboxing.Enum Bar
Enum a |
newtype EnumRep rep a Source #
A newtype wrapper to be used with DerivingVia
.
Usage:
data Direction = North | South | East | West deriving Enum deriving Data.Vector.Unboxing.Unboxable via Data.Vector.Unboxing.EnumRep Int8 Bar
EnumRep a |
Accessors
Length information
Extracting subvectors (slicing)
Overlapping
Construction
Initialisation
clone :: (PrimMonad m, Unboxable a) => MVector (PrimState m) a -> m (MVector (PrimState m) a) Source #
Growing
grow :: (PrimMonad m, Unboxable a) => MVector (PrimState m) a -> Int -> m (MVector (PrimState m) a) Source #
unsafeGrow :: (PrimMonad m, Unboxable a) => MVector (PrimState m) a -> Int -> m (MVector (PrimState m) a) Source #
Restricting memory usage
Zipping and unzipping
zip3 :: (Unboxable a, Unboxable b, Unboxable c) => MVector s a -> MVector s b -> MVector s c -> MVector s (a, b, c) Source #
zip4 :: (Unboxable a, Unboxable b, Unboxable c, Unboxable d) => MVector s a -> MVector s b -> MVector s c -> MVector s d -> MVector s (a, b, c, d) Source #
zip5 :: (Unboxable a, Unboxable b, Unboxable c, Unboxable d, Unboxable e) => MVector s a -> MVector s b -> MVector s c -> MVector s d -> MVector s e -> MVector s (a, b, c, d, e) Source #
zip6 :: (Unboxable a, Unboxable b, Unboxable c, Unboxable d, Unboxable e, Unboxable f) => MVector s a -> MVector s b -> MVector s c -> MVector s d -> MVector s e -> MVector s f -> MVector s (a, b, c, d, e, f) Source #
unzip3 :: (Unboxable a, Unboxable b, Unboxable c) => MVector s (a, b, c) -> (MVector s a, MVector s b, MVector s c) Source #
unzip4 :: (Unboxable a, Unboxable b, Unboxable c, Unboxable d) => MVector s (a, b, c, d) -> (MVector s a, MVector s b, MVector s c, MVector s d) Source #
unzip5 :: (Unboxable a, Unboxable b, Unboxable c, Unboxable d, Unboxable e) => MVector s (a, b, c, d, e) -> (MVector s a, MVector s b, MVector s c, MVector s d, MVector s e) Source #
unzip6 :: (Unboxable a, Unboxable b, Unboxable c, Unboxable d, Unboxable e, Unboxable f) => MVector s (a, b, c, d, e, f) -> (MVector s a, MVector s b, MVector s c, MVector s d, MVector s e, MVector s f) Source #
Accessing individual elements
unsafeModify :: (PrimMonad m, Unboxable a) => MVector (PrimState m) a -> (a -> a) -> Int -> m () Source #
Modifying vectors
Filling and copying
Conversions from/to other vector types
coerceMVector :: (Coercible a b, Unboxable a, Unboxable b, CoercibleRep a ~ CoercibleRep b, Rep a ~ Rep b) => MVector s a -> MVector s b Source #
liftCoercionM :: (Unboxable a, Unboxable b, CoercibleRep a ~ CoercibleRep b, Rep a ~ Rep b) => Coercion a b -> Coercion (MVector s a) (MVector s b) Source #
mVectorCoercion :: (Coercible a b, Unboxable a, Unboxable b, CoercibleRep a ~ CoercibleRep b, Rep a ~ Rep b) => Coercion (MVector s a) (MVector s b) Source #
toUnboxedMVector :: (Unboxable a, Rep a ~ a, IsTrivial a ~ True) => MVector s a -> MVector s a Source #