unboxing-vector-0.2.0.0: A newtype-friendly variant of unboxed vectors
Safe HaskellNone
LanguageHaskell2010

Data.Vector.Unboxing.Mutable

Synopsis

Documentation

data MVector s a Source #

Instances

Instances details
Unboxable a => MVector MVector a Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Methods

basicLength :: MVector s a -> Int

basicUnsafeSlice :: Int -> Int -> MVector s a -> MVector s a

basicOverlaps :: MVector s a -> MVector s a -> Bool

basicUnsafeNew :: Int -> ST s (MVector s a)

basicInitialize :: MVector s a -> ST s ()

basicUnsafeReplicate :: Int -> a -> ST s (MVector s a)

basicUnsafeRead :: MVector s a -> Int -> ST s a

basicUnsafeWrite :: MVector s a -> Int -> a -> ST s ()

basicClear :: MVector s a -> ST s ()

basicSet :: MVector s a -> a -> ST s ()

basicUnsafeCopy :: MVector s a -> MVector s a -> ST s ()

basicUnsafeMove :: MVector s a -> MVector s a -> ST s ()

basicUnsafeGrow :: MVector s a -> Int -> ST s (MVector s a)

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.

Associated Types

type Rep a Source #

The underlying type of a. Must be an instance of Unbox.

Instances

Instances details
Unboxable All Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep All 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep All = Bool
Unboxable Any Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep Any 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep Any = Bool
Unboxable Int16 Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep Int16 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep Int16 = Int16
Unboxable Int32 Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep Int32 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep Int32 = Int32
Unboxable Int64 Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep Int64 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep Int64 = Int64
Unboxable Int8 Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep Int8 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep Int8 = Int8
Unboxable Word16 Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep Word16 
Instance details

Defined in Data.Vector.Unboxing.Internal

Unboxable Word32 Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep Word32 
Instance details

Defined in Data.Vector.Unboxing.Internal

Unboxable Word64 Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep Word64 
Instance details

Defined in Data.Vector.Unboxing.Internal

Unboxable Word8 Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep Word8 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep Word8 = Word8
Unboxable Ordering Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep Ordering 
Instance details

Defined in Data.Vector.Unboxing.Internal

Unboxable () Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep () 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep () = ()

Methods

unboxingFrom :: () -> Rep ()

unboxingTo :: Rep () -> ()

Unboxable Bool Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep Bool 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep Bool = Bool
Unboxable Char Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep Char 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep Char = Char
Unboxable Double Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep Double 
Instance details

Defined in Data.Vector.Unboxing.Internal

Unboxable Float Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep Float 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep Float = Float
Unboxable Int Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep Int 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep Int = Int
Unboxable Word Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep Word 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep Word = Word
Unboxable a => Unboxable (Complex a) Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (Complex a) 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep (Complex a) = Complex (Rep a)
Unboxable a => Unboxable (Identity a) Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (Identity a) 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep (Identity a) = Rep a
Unboxable a => Unboxable (Down a) Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (Down a) 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep (Down a) = Rep a

Methods

unboxingFrom :: Down a -> Rep (Down a)

unboxingTo :: Rep (Down a) -> Down a

Unboxable a => Unboxable (First a) Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (First a) 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep (First a) = Rep a

Methods

unboxingFrom :: First a -> Rep (First a)

unboxingTo :: Rep (First a) -> First a

Unboxable a => Unboxable (Last a) Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (Last a) 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep (Last a) = Rep a

Methods

unboxingFrom :: Last a -> Rep (Last a)

unboxingTo :: Rep (Last a) -> Last a

Unboxable a => Unboxable (Max a) Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (Max a) 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep (Max a) = Rep a

Methods

unboxingFrom :: Max a -> Rep (Max a)

unboxingTo :: Rep (Max a) -> Max a

Unboxable a => Unboxable (Min a) Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (Min a) 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep (Min a) = Rep a

Methods

unboxingFrom :: Min a -> Rep (Min a)

unboxingTo :: Rep (Min a) -> Min a

Unboxable a => Unboxable (WrappedMonoid a) Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (WrappedMonoid a) 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep (WrappedMonoid a) = Rep a
Unboxable a => Unboxable (Dual a) Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (Dual a) 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep (Dual a) = Rep a

Methods

unboxingFrom :: Dual a -> Rep (Dual a)

unboxingTo :: Rep (Dual a) -> Dual a

Unboxable a => Unboxable (Product a) Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (Product a) 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep (Product a) = Rep a
Unboxable a => Unboxable (Sum a) Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (Sum a) 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep (Sum a) = Rep a

Methods

unboxingFrom :: Sum a -> Rep (Sum a)

unboxingTo :: Rep (Sum a) -> Sum a

Enum a => Unboxable (Enum a) Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (Enum a) 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep (Enum a) = Int

Methods

unboxingFrom :: Enum a -> Rep (Enum a)

unboxingTo :: Rep (Enum a) -> Enum a

(Generic a, Unbox (Rep' (Rep a)), Unboxable' (Rep a)) => Unboxable (Generics a) Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (Generics a) 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep (Generics a)
(Unboxable a, Unboxable b) => Unboxable (Arg a b) Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (Arg a b) 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep (Arg a b) = (Rep a, Rep b)

Methods

unboxingFrom :: Arg a b -> Rep (Arg a b)

unboxingTo :: Rep (Arg a b) -> Arg a b

(Enum a, Integral rep, Unbox rep) => Unboxable (EnumRep rep a) Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (EnumRep rep a) 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep (EnumRep rep a) = rep

Methods

unboxingFrom :: EnumRep rep a -> Rep (EnumRep rep a)

unboxingTo :: Rep (EnumRep rep a) -> EnumRep rep a

(Unboxable a, Unboxable b) => Unboxable (a, b) Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (a, b) 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep (a, b) = (Rep a, Rep b)

Methods

unboxingFrom :: (a, b) -> Rep (a, b)

unboxingTo :: Rep (a, b) -> (a, b)

Unboxable a => Unboxable (Const a b) Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (Const a b) 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep (Const a b) = Rep a

Methods

unboxingFrom :: Const a b -> Rep (Const a b)

unboxingTo :: Rep (Const a b) -> Const a b

Unboxable (f a) => Unboxable (Alt f a) Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (Alt f a) 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep (Alt f a) = Rep (f a)

Methods

unboxingFrom :: Alt f a -> Rep (Alt f a)

unboxingTo :: Rep (Alt f a) -> Alt f a

(Unboxable a, Unboxable b, Unboxable c) => Unboxable (a, b, c) Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (a, b, c) 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep (a, b, c) = (Rep a, Rep b, Rep c)

Methods

unboxingFrom :: (a, b, c) -> Rep (a, b, c)

unboxingTo :: Rep (a, b, c) -> (a, b, c)

(Unboxable a, Unboxable b, Unboxable c, Unboxable d) => Unboxable (a, b, c, d) Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (a, b, c, d) 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep (a, b, c, d) = (Rep a, Rep b, Rep c, Rep d)

Methods

unboxingFrom :: (a, b, c, d) -> Rep (a, b, c, d)

unboxingTo :: Rep (a, b, c, d) -> (a, b, c, d)

Unboxable (f (g a)) => Unboxable (Compose f g a) Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (Compose f g a) 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep (Compose f g a) = Rep (f (g a))

Methods

unboxingFrom :: Compose f g a -> Rep (Compose f g a)

unboxingTo :: Rep (Compose f g a) -> Compose f g a

(Unboxable a, Unboxable b, Unboxable c, Unboxable d, Unboxable e) => Unboxable (a, b, c, d, e) Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (a, b, c, d, e) 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep (a, b, c, d, e) = (Rep a, Rep b, Rep c, Rep d, Rep e)

Methods

unboxingFrom :: (a, b, c, d, e) -> Rep (a, b, c, d, e)

unboxingTo :: Rep (a, b, c, d, e) -> (a, b, c, d, e)

(Unboxable a, Unboxable b, Unboxable c, Unboxable d, Unboxable e, Unboxable f) => Unboxable (a, b, c, d, e, f) Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (a, b, c, d, e, f) 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep (a, b, c, d, e, f) = (Rep a, Rep b, Rep c, Rep d, Rep e, Rep f)

Methods

unboxingFrom :: (a, b, c, d, e, f) -> Rep (a, b, c, d, e, f)

unboxingTo :: Rep (a, b, c, d, e, f) -> (a, b, c, d, e, f)

newtype Generics a Source #

A newtype wrapper to be used with DerivingVia.

Usage:

data Bar = Bar !Int !Int
  deriving Generic
  deriving Unboxable via Generics Bar

Constructors

Generics a 

Instances

Instances details
(Generic a, Unbox (Rep' (Rep a)), Unboxable' (Rep a)) => Unboxable (Generics a) Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (Generics a) 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep (Generics a)
type Rep (Generics a) Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep (Generics a)

newtype Enum a Source #

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

Constructors

Enum a 

Instances

Instances details
Enum a => Unboxable (Enum a) Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (Enum a) 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep (Enum a) = Int

Methods

unboxingFrom :: Enum a -> Rep (Enum a)

unboxingTo :: Rep (Enum a) -> Enum a

type Rep (Enum a) Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep (Enum a) = Int

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

Constructors

EnumRep a 

Instances

Instances details
(Enum a, Integral rep, Unbox rep) => Unboxable (EnumRep rep a) Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (EnumRep rep a) 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep (EnumRep rep a) = rep

Methods

unboxingFrom :: EnumRep rep a -> Rep (EnumRep rep a)

unboxingTo :: Rep (EnumRep rep a) -> EnumRep rep a

type Rep (EnumRep rep a) Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

type Rep (EnumRep rep a) = rep

Accessors

Length information

Extracting subvectors (slicing)

slice :: Unboxable a => Int -> Int -> MVector s a -> MVector s a Source #

init :: Unboxable a => MVector s a -> MVector s a Source #

tail :: Unboxable a => MVector s a -> MVector s a Source #

take :: Unboxable a => Int -> MVector s a -> MVector s a Source #

drop :: Unboxable a => Int -> MVector s a -> MVector s a Source #

splitAt :: Unboxable a => Int -> MVector s a -> (MVector s a, MVector s a) Source #

unsafeSlice :: Unboxable a => Int -> Int -> MVector s a -> MVector s a Source #

Overlapping

overlaps :: Unboxable a => MVector s a -> MVector s a -> Bool Source #

Construction

Initialisation

new :: (PrimMonad m, Unboxable a) => Int -> m (MVector (PrimState m) a) Source #

replicate :: (PrimMonad m, Unboxable a) => Int -> a -> m (MVector (PrimState m) a) Source #

replicateM :: (PrimMonad m, Unboxable a) => Int -> 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 #

Restricting memory usage

clear :: (PrimMonad m, Unboxable a) => MVector (PrimState m) a -> m () Source #

Zipping and unzipping

zip :: (Unboxable a, Unboxable b) => MVector s a -> MVector s b -> MVector s (a, b) Source #

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 #

unzip :: (Unboxable a, Unboxable b) => MVector s (a, b) -> (MVector s a, MVector s b) 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

read :: (PrimMonad m, Unboxable a) => MVector (PrimState m) a -> Int -> m a Source #

write :: (PrimMonad m, Unboxable a) => MVector (PrimState m) a -> Int -> a -> m () Source #

modify :: (PrimMonad m, Unboxable a) => MVector (PrimState m) a -> (a -> a) -> Int -> m () Source #

swap :: (PrimMonad m, Unboxable a) => MVector (PrimState m) a -> Int -> Int -> m () Source #

unsafeRead :: (PrimMonad m, Unboxable a) => MVector (PrimState m) a -> Int -> m a Source #

unsafeWrite :: (PrimMonad m, Unboxable a) => MVector (PrimState m) a -> Int -> a -> m () Source #

unsafeModify :: (PrimMonad m, Unboxable a) => MVector (PrimState m) a -> (a -> a) -> Int -> m () Source #

unsafeSwap :: (PrimMonad m, Unboxable a) => MVector (PrimState m) a -> Int -> Int -> m () Source #

Modifying vectors

Filling and copying

set :: (PrimMonad m, Unboxable a) => MVector (PrimState m) a -> a -> m () Source #

copy Source #

Arguments

:: (PrimMonad m, Unboxable a) 
=> MVector (PrimState m) a

target

-> MVector (PrimState m) a

source

-> m () 

move Source #

Arguments

:: (PrimMonad m, Unboxable a) 
=> MVector (PrimState m) a

target

-> MVector (PrimState m) a

source

-> m () 

unsafeCopy Source #

Arguments

:: (PrimMonad m, Unboxable a) 
=> MVector (PrimState m) a

target

-> MVector (PrimState m) a

source

-> m () 

unsafeMove Source #

Arguments

:: (PrimMonad m, Unboxable a) 
=> MVector (PrimState m) a

target

-> MVector (PrimState m) a

source

-> m () 

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 #

fromUnboxedMVector :: (Unboxable a, Rep a ~ a, IsTrivial a ~ 'True) => MVector s a -> MVector s a Source #

coercionWithUnboxedMVector :: (Unboxable a, Rep a ~ a, IsTrivial a ~ 'True) => Coercion (MVector s a) (MVector s a) Source #