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

Safe HaskellNone
LanguageHaskell2010

Data.Vector.Unboxing.Mutable

Contents

Synopsis

Documentation

data MVector s a Source #

Instances
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 :: PrimMonad m => Int -> m (MVector (PrimState m) a) #

basicInitialize :: PrimMonad m => MVector (PrimState m) a -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> a -> m (MVector (PrimState m) a) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) a -> Int -> m a #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) a -> Int -> a -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) a -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) a -> a -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) a -> MVector (PrimState m) a -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) a -> MVector (PrimState m) a -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) a -> Int -> m (MVector (PrimState m) 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
Unboxable Bool Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep Bool :: Type Source #

type CoercibleRep Bool :: Type

type IsTrivial Bool :: Bool

Unboxable Char Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep Char :: Type Source #

type CoercibleRep Char :: Type

type IsTrivial Char :: Bool

Unboxable Double Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep Double :: Type Source #

type CoercibleRep Double :: Type

type IsTrivial Double :: Bool

Unboxable Float Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep Float :: Type Source #

type CoercibleRep Float :: Type

type IsTrivial Float :: Bool

Unboxable Int Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep Int :: Type Source #

type CoercibleRep Int :: Type

type IsTrivial Int :: Bool

Unboxable Int8 Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep Int8 :: Type Source #

type CoercibleRep Int8 :: Type

type IsTrivial Int8 :: Bool

Unboxable Int16 Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep Int16 :: Type Source #

type CoercibleRep Int16 :: Type

type IsTrivial Int16 :: Bool

Unboxable Int32 Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep Int32 :: Type Source #

type CoercibleRep Int32 :: Type

type IsTrivial Int32 :: Bool

Unboxable Int64 Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep Int64 :: Type Source #

type CoercibleRep Int64 :: Type

type IsTrivial Int64 :: Bool

Unboxable Ordering Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep Ordering :: Type Source #

type CoercibleRep Ordering :: Type

type IsTrivial Ordering :: Bool

Unboxable Word Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep Word :: Type Source #

type CoercibleRep Word :: Type

type IsTrivial Word :: Bool

Unboxable Word8 Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep Word8 :: Type Source #

type CoercibleRep Word8 :: Type

type IsTrivial Word8 :: Bool

Unboxable Word16 Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep Word16 :: Type Source #

type CoercibleRep Word16 :: Type

type IsTrivial Word16 :: Bool

Unboxable Word32 Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep Word32 :: Type Source #

type CoercibleRep Word32 :: Type

type IsTrivial Word32 :: Bool

Unboxable Word64 Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep Word64 :: Type Source #

type CoercibleRep Word64 :: Type

type IsTrivial Word64 :: Bool

Unboxable () Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep () :: Type Source #

type CoercibleRep () :: Type

type IsTrivial () :: Bool

Methods

unboxingFrom :: () -> Rep ()

unboxingTo :: Rep () -> ()

Unboxable All Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep All :: Type Source #

type CoercibleRep All :: Type

type IsTrivial All :: Bool

Unboxable Any Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep Any :: Type Source #

type CoercibleRep Any :: Type

type IsTrivial Any :: Bool

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

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (Complex a) :: Type Source #

type CoercibleRep (Complex a) :: Type

type IsTrivial (Complex a) :: Bool

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

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (Min a) :: Type Source #

type CoercibleRep (Min a) :: Type

type IsTrivial (Min a) :: Bool

Methods

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

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

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

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (Max a) :: Type Source #

type CoercibleRep (Max a) :: Type

type IsTrivial (Max a) :: Bool

Methods

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

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

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

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (First a) :: Type Source #

type CoercibleRep (First a) :: Type

type IsTrivial (First a) :: Bool

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) :: Type Source #

type CoercibleRep (Last a) :: Type

type IsTrivial (Last a) :: Bool

Methods

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

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

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

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (WrappedMonoid a) :: Type Source #

type CoercibleRep (WrappedMonoid a) :: Type

type IsTrivial (WrappedMonoid a) :: Bool

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

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (Identity a) :: Type Source #

type CoercibleRep (Identity a) :: Type

type IsTrivial (Identity a) :: Bool

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

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (Dual a) :: Type Source #

type CoercibleRep (Dual a) :: Type

type IsTrivial (Dual a) :: Bool

Methods

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

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

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

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (Sum a) :: Type Source #

type CoercibleRep (Sum a) :: Type

type IsTrivial (Sum a) :: Bool

Methods

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

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

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

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (Product a) :: Type Source #

type CoercibleRep (Product a) :: Type

type IsTrivial (Product a) :: Bool

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

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (Down a) :: Type Source #

type CoercibleRep (Down a) :: Type

type IsTrivial (Down a) :: Bool

Methods

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

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

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

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (Enum a) :: Type Source #

type CoercibleRep (Enum a) :: Type

type IsTrivial (Enum a) :: Bool

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) :: Type Source #

type CoercibleRep (Generics a) :: Type

type IsTrivial (Generics a) :: Bool

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

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (a, b) :: Type Source #

type CoercibleRep (a, b) :: Type

type IsTrivial (a, b) :: Bool

Methods

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

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

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

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (Arg a b) :: Type Source #

type CoercibleRep (Arg a b) :: Type

type IsTrivial (Arg a b) :: Bool

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) :: Type Source #

type CoercibleRep (EnumRep rep a) :: Type

type IsTrivial (EnumRep rep a) :: Bool

Methods

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

unboxingTo :: Rep (EnumRep rep a) -> EnumRep rep 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) :: Type Source #

type CoercibleRep (a, b, c) :: Type

type IsTrivial (a, b, c) :: Bool

Methods

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

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

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

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (Const a b) :: Type Source #

type CoercibleRep (Const a b) :: Type

type IsTrivial (Const a b) :: Bool

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) :: Type Source #

type CoercibleRep (Alt f a) :: Type

type IsTrivial (Alt f a) :: Bool

Methods

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

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

(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) :: Type Source #

type CoercibleRep (a, b, c, d) :: Type

type IsTrivial (a, b, c, d) :: Bool

Methods

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

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

(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) :: Type Source #

type CoercibleRep (a, b, c, d, e) :: Type

type IsTrivial (a, b, c, d, e) :: Bool

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 (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) :: Type Source #

type CoercibleRep (Compose f g a) :: Type

type IsTrivial (Compose f g a) :: Bool

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 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) :: Type Source #

type CoercibleRep (a, b, c, d, e, f) :: Type

type IsTrivial (a, b, c, d, e, f) :: Bool

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
(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) :: Type Source #

type CoercibleRep (Generics a) :: Type

type IsTrivial (Generics a) :: Bool

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
Enum a => Unboxable (Enum a) Source # 
Instance details

Defined in Data.Vector.Unboxing.Internal

Associated Types

type Rep (Enum a) :: Type Source #

type CoercibleRep (Enum a) :: Type

type IsTrivial (Enum a) :: Bool

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
(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) :: Type Source #

type CoercibleRep (EnumRep rep a) :: Type

type IsTrivial (EnumRep rep a) :: Bool

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 #