vector-0.12.1.2: Efficient Arrays
Copyright(c) Roman Leshchinskiy 2008-2010
LicenseBSD-style
MaintainerRoman Leshchinskiy <rl@cse.unsw.edu.au>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Vector.Primitive.Mutable

Description

Mutable primitive vectors.

Synopsis

Mutable vectors of primitive types

data MVector s a Source #

Mutable vectors of primitive types.

Constructors

MVector !Int !Int !(MutableByteArray s)

offset, length, underlying mutable byte array

Instances

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

Defined in Data.Vector.Primitive.Mutable

Methods

basicLength :: MVector s a -> Int Source #

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

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

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

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

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

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

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

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

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

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

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

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

NFData1 (MVector s) Source # 
Instance details

Defined in Data.Vector.Primitive.Mutable

Methods

liftRnf :: (a -> ()) -> MVector s a -> ()

NFData (MVector s a) Source # 
Instance details

Defined in Data.Vector.Primitive.Mutable

Methods

rnf :: MVector s a -> ()

class Prim a Source #

Class of types supporting primitive array operations. This includes interfacing with GC-managed memory (functions suffixed with ByteArray#) and interfacing with unmanaged memory (functions suffixed with Addr#). Endianness is platform-dependent.

Instances

Instances details
Prim Char 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: Char -> Int# Source #

alignment# :: Char -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> Char Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Char #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> Char -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Char -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> Char Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Char #) Source #

writeOffAddr# :: Addr# -> Int# -> Char -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> Char -> State# s -> State# s Source #

Prim Double 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: Double -> Int# Source #

alignment# :: Double -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> Double Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Double #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> Double -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Double -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> Double Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Double #) Source #

writeOffAddr# :: Addr# -> Int# -> Double -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> Double -> State# s -> State# s Source #

Prim Float 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: Float -> Int# Source #

alignment# :: Float -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> Float Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Float #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> Float -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Float -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> Float Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Float #) Source #

writeOffAddr# :: Addr# -> Int# -> Float -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> Float -> State# s -> State# s Source #

Prim Int 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: Int -> Int# Source #

alignment# :: Int -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> Int Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Int #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> Int -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Int -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> Int Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Int #) Source #

writeOffAddr# :: Addr# -> Int# -> Int -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> Int -> State# s -> State# s Source #

Prim Int8 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: Int8 -> Int# Source #

alignment# :: Int8 -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> Int8 Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Int8 #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> Int8 -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Int8 -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> Int8 Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Int8 #) Source #

writeOffAddr# :: Addr# -> Int# -> Int8 -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> Int8 -> State# s -> State# s Source #

Prim Int16 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: Int16 -> Int# Source #

alignment# :: Int16 -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> Int16 Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Int16 #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> Int16 -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Int16 -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> Int16 Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Int16 #) Source #

writeOffAddr# :: Addr# -> Int# -> Int16 -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> Int16 -> State# s -> State# s Source #

Prim Int32 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: Int32 -> Int# Source #

alignment# :: Int32 -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> Int32 Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Int32 #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> Int32 -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Int32 -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> Int32 Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Int32 #) Source #

writeOffAddr# :: Addr# -> Int# -> Int32 -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> Int32 -> State# s -> State# s Source #

Prim Int64 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: Int64 -> Int# Source #

alignment# :: Int64 -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> Int64 Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Int64 #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> Int64 -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Int64 -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> Int64 Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Int64 #) Source #

writeOffAddr# :: Addr# -> Int# -> Int64 -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> Int64 -> State# s -> State# s Source #

Prim Word 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: Word -> Int# Source #

alignment# :: Word -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> Word Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Word #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> Word -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Word -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> Word Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Word #) Source #

writeOffAddr# :: Addr# -> Int# -> Word -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> Word -> State# s -> State# s Source #

Prim Word8 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: Word8 -> Int# Source #

alignment# :: Word8 -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> Word8 Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Word8 #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> Word8 -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Word8 -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> Word8 Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Word8 #) Source #

writeOffAddr# :: Addr# -> Int# -> Word8 -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> Word8 -> State# s -> State# s Source #

Prim Word16 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: Word16 -> Int# Source #

alignment# :: Word16 -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> Word16 Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Word16 #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> Word16 -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Word16 -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> Word16 Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Word16 #) Source #

writeOffAddr# :: Addr# -> Int# -> Word16 -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> Word16 -> State# s -> State# s Source #

Prim Word32 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: Word32 -> Int# Source #

alignment# :: Word32 -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> Word32 Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Word32 #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> Word32 -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Word32 -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> Word32 Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Word32 #) Source #

writeOffAddr# :: Addr# -> Int# -> Word32 -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> Word32 -> State# s -> State# s Source #

Prim Word64 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: Word64 -> Int# Source #

alignment# :: Word64 -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> Word64 Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Word64 #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> Word64 -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Word64 -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> Word64 Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Word64 #) Source #

writeOffAddr# :: Addr# -> Int# -> Word64 -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> Word64 -> State# s -> State# s Source #

Prim CInt 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CInt -> Int# Source #

alignment# :: CInt -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CInt Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CInt #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CInt -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CInt -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CInt Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CInt #) Source #

writeOffAddr# :: Addr# -> Int# -> CInt -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CInt -> State# s -> State# s Source #

Prim CBool 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CBool -> Int# Source #

alignment# :: CBool -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CBool Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CBool #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CBool -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CBool -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CBool Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CBool #) Source #

writeOffAddr# :: Addr# -> Int# -> CBool -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CBool -> State# s -> State# s Source #

Prim CChar 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CChar -> Int# Source #

alignment# :: CChar -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CChar Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CChar #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CChar -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CChar -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CChar Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CChar #) Source #

writeOffAddr# :: Addr# -> Int# -> CChar -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CChar -> State# s -> State# s Source #

Prim CClock 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CClock -> Int# Source #

alignment# :: CClock -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CClock Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CClock #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CClock -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CClock -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CClock Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CClock #) Source #

writeOffAddr# :: Addr# -> Int# -> CClock -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CClock -> State# s -> State# s Source #

Prim CDouble 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CDouble -> Int# Source #

alignment# :: CDouble -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CDouble Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CDouble #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CDouble -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CDouble -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CDouble Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CDouble #) Source #

writeOffAddr# :: Addr# -> Int# -> CDouble -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CDouble -> State# s -> State# s Source #

Prim CFloat 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CFloat -> Int# Source #

alignment# :: CFloat -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CFloat Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CFloat #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CFloat -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CFloat -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CFloat Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CFloat #) Source #

writeOffAddr# :: Addr# -> Int# -> CFloat -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CFloat -> State# s -> State# s Source #

Prim CIntMax 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CIntMax -> Int# Source #

alignment# :: CIntMax -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CIntMax Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CIntMax #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CIntMax -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CIntMax -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CIntMax Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CIntMax #) Source #

writeOffAddr# :: Addr# -> Int# -> CIntMax -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CIntMax -> State# s -> State# s Source #

Prim CIntPtr 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CIntPtr -> Int# Source #

alignment# :: CIntPtr -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CIntPtr Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CIntPtr #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CIntPtr -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CIntPtr -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CIntPtr Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CIntPtr #) Source #

writeOffAddr# :: Addr# -> Int# -> CIntPtr -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CIntPtr -> State# s -> State# s Source #

Prim CLLong 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CLLong -> Int# Source #

alignment# :: CLLong -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CLLong Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CLLong #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CLLong -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CLLong -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CLLong Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CLLong #) Source #

writeOffAddr# :: Addr# -> Int# -> CLLong -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CLLong -> State# s -> State# s Source #

Prim CLong 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CLong -> Int# Source #

alignment# :: CLong -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CLong Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CLong #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CLong -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CLong -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CLong Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CLong #) Source #

writeOffAddr# :: Addr# -> Int# -> CLong -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CLong -> State# s -> State# s Source #

Prim CPtrdiff 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CPtrdiff -> Int# Source #

alignment# :: CPtrdiff -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CPtrdiff Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CPtrdiff #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CPtrdiff -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CPtrdiff -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CPtrdiff Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CPtrdiff #) Source #

writeOffAddr# :: Addr# -> Int# -> CPtrdiff -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CPtrdiff -> State# s -> State# s Source #

Prim CSChar 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CSChar -> Int# Source #

alignment# :: CSChar -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CSChar Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CSChar #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CSChar -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CSChar -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CSChar Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CSChar #) Source #

writeOffAddr# :: Addr# -> Int# -> CSChar -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CSChar -> State# s -> State# s Source #

Prim CSUSeconds 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CSUSeconds -> Int# Source #

alignment# :: CSUSeconds -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CSUSeconds Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CSUSeconds #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CSUSeconds -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CSUSeconds -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CSUSeconds Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CSUSeconds #) Source #

writeOffAddr# :: Addr# -> Int# -> CSUSeconds -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CSUSeconds -> State# s -> State# s Source #

Prim CShort 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CShort -> Int# Source #

alignment# :: CShort -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CShort Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CShort #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CShort -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CShort -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CShort Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CShort #) Source #

writeOffAddr# :: Addr# -> Int# -> CShort -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CShort -> State# s -> State# s Source #

Prim CSigAtomic 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CSigAtomic -> Int# Source #

alignment# :: CSigAtomic -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CSigAtomic Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CSigAtomic #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CSigAtomic -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CSigAtomic -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CSigAtomic Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CSigAtomic #) Source #

writeOffAddr# :: Addr# -> Int# -> CSigAtomic -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CSigAtomic -> State# s -> State# s Source #

Prim CSize 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CSize -> Int# Source #

alignment# :: CSize -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CSize Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CSize #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CSize -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CSize -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CSize Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CSize #) Source #

writeOffAddr# :: Addr# -> Int# -> CSize -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CSize -> State# s -> State# s Source #

Prim CTime 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CTime -> Int# Source #

alignment# :: CTime -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CTime Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CTime #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CTime -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CTime -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CTime Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CTime #) Source #

writeOffAddr# :: Addr# -> Int# -> CTime -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CTime -> State# s -> State# s Source #

Prim CUChar 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CUChar -> Int# Source #

alignment# :: CUChar -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CUChar Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CUChar #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CUChar -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CUChar -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CUChar Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CUChar #) Source #

writeOffAddr# :: Addr# -> Int# -> CUChar -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CUChar -> State# s -> State# s Source #

Prim CUInt 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CUInt -> Int# Source #

alignment# :: CUInt -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CUInt Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CUInt #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CUInt -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CUInt -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CUInt Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CUInt #) Source #

writeOffAddr# :: Addr# -> Int# -> CUInt -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CUInt -> State# s -> State# s Source #

Prim CUIntMax 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CUIntMax -> Int# Source #

alignment# :: CUIntMax -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CUIntMax Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CUIntMax #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CUIntMax -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CUIntMax -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CUIntMax Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CUIntMax #) Source #

writeOffAddr# :: Addr# -> Int# -> CUIntMax -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CUIntMax -> State# s -> State# s Source #

Prim CUIntPtr 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CUIntPtr -> Int# Source #

alignment# :: CUIntPtr -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CUIntPtr Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CUIntPtr #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CUIntPtr -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CUIntPtr -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CUIntPtr Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CUIntPtr #) Source #

writeOffAddr# :: Addr# -> Int# -> CUIntPtr -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CUIntPtr -> State# s -> State# s Source #

Prim CULLong 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CULLong -> Int# Source #

alignment# :: CULLong -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CULLong Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CULLong #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CULLong -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CULLong -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CULLong Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CULLong #) Source #

writeOffAddr# :: Addr# -> Int# -> CULLong -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CULLong -> State# s -> State# s Source #

Prim CULong 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CULong -> Int# Source #

alignment# :: CULong -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CULong Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CULong #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CULong -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CULong -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CULong Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CULong #) Source #

writeOffAddr# :: Addr# -> Int# -> CULong -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CULong -> State# s -> State# s Source #

Prim CUSeconds 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CUSeconds -> Int# Source #

alignment# :: CUSeconds -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CUSeconds Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CUSeconds #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CUSeconds -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CUSeconds -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CUSeconds Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CUSeconds #) Source #

writeOffAddr# :: Addr# -> Int# -> CUSeconds -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CUSeconds -> State# s -> State# s Source #

Prim CUShort 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CUShort -> Int# Source #

alignment# :: CUShort -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CUShort Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CUShort #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CUShort -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CUShort -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CUShort Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CUShort #) Source #

writeOffAddr# :: Addr# -> Int# -> CUShort -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CUShort -> State# s -> State# s Source #

Prim CWchar 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CWchar -> Int# Source #

alignment# :: CWchar -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CWchar Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CWchar #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CWchar -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CWchar -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CWchar Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CWchar #) Source #

writeOffAddr# :: Addr# -> Int# -> CWchar -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CWchar -> State# s -> State# s Source #

Prim CBlkCnt 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CBlkCnt -> Int# Source #

alignment# :: CBlkCnt -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CBlkCnt Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CBlkCnt #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CBlkCnt -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CBlkCnt -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CBlkCnt Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CBlkCnt #) Source #

writeOffAddr# :: Addr# -> Int# -> CBlkCnt -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CBlkCnt -> State# s -> State# s Source #

Prim CBlkSize 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CBlkSize -> Int# Source #

alignment# :: CBlkSize -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CBlkSize Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CBlkSize #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CBlkSize -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CBlkSize -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CBlkSize Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CBlkSize #) Source #

writeOffAddr# :: Addr# -> Int# -> CBlkSize -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CBlkSize -> State# s -> State# s Source #

Prim CCc 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CCc -> Int# Source #

alignment# :: CCc -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CCc Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CCc #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CCc -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CCc -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CCc Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CCc #) Source #

writeOffAddr# :: Addr# -> Int# -> CCc -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CCc -> State# s -> State# s Source #

Prim CClockId 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CClockId -> Int# Source #

alignment# :: CClockId -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CClockId Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CClockId #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CClockId -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CClockId -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CClockId Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CClockId #) Source #

writeOffAddr# :: Addr# -> Int# -> CClockId -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CClockId -> State# s -> State# s Source #

Prim CDev 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CDev -> Int# Source #

alignment# :: CDev -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CDev Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CDev #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CDev -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CDev -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CDev Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CDev #) Source #

writeOffAddr# :: Addr# -> Int# -> CDev -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CDev -> State# s -> State# s Source #

Prim CFsBlkCnt 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CFsBlkCnt -> Int# Source #

alignment# :: CFsBlkCnt -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CFsBlkCnt Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CFsBlkCnt #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CFsBlkCnt -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CFsBlkCnt -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CFsBlkCnt Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CFsBlkCnt #) Source #

writeOffAddr# :: Addr# -> Int# -> CFsBlkCnt -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CFsBlkCnt -> State# s -> State# s Source #

Prim CFsFilCnt 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CFsFilCnt -> Int# Source #

alignment# :: CFsFilCnt -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CFsFilCnt Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CFsFilCnt #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CFsFilCnt -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CFsFilCnt -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CFsFilCnt Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CFsFilCnt #) Source #

writeOffAddr# :: Addr# -> Int# -> CFsFilCnt -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CFsFilCnt -> State# s -> State# s Source #

Prim CGid 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CGid -> Int# Source #

alignment# :: CGid -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CGid Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CGid #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CGid -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CGid -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CGid Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CGid #) Source #

writeOffAddr# :: Addr# -> Int# -> CGid -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CGid -> State# s -> State# s Source #

Prim CId 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CId -> Int# Source #

alignment# :: CId -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CId Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CId #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CId -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CId -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CId Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CId #) Source #

writeOffAddr# :: Addr# -> Int# -> CId -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CId -> State# s -> State# s Source #

Prim CIno 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CIno -> Int# Source #

alignment# :: CIno -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CIno Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CIno #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CIno -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CIno -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CIno Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CIno #) Source #

writeOffAddr# :: Addr# -> Int# -> CIno -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CIno -> State# s -> State# s Source #

Prim CKey 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CKey -> Int# Source #

alignment# :: CKey -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CKey Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CKey #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CKey -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CKey -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CKey Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CKey #) Source #

writeOffAddr# :: Addr# -> Int# -> CKey -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CKey -> State# s -> State# s Source #

Prim CMode 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CMode -> Int# Source #

alignment# :: CMode -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CMode Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CMode #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CMode -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CMode -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CMode Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CMode #) Source #

writeOffAddr# :: Addr# -> Int# -> CMode -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CMode -> State# s -> State# s Source #

Prim CNlink 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CNlink -> Int# Source #

alignment# :: CNlink -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CNlink Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CNlink #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CNlink -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CNlink -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CNlink Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CNlink #) Source #

writeOffAddr# :: Addr# -> Int# -> CNlink -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CNlink -> State# s -> State# s Source #

Prim COff 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: COff -> Int# Source #

alignment# :: COff -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> COff Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, COff #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> COff -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> COff -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> COff Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, COff #) Source #

writeOffAddr# :: Addr# -> Int# -> COff -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> COff -> State# s -> State# s Source #

Prim CPid 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CPid -> Int# Source #

alignment# :: CPid -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CPid Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CPid #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CPid -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CPid -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CPid Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CPid #) Source #

writeOffAddr# :: Addr# -> Int# -> CPid -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CPid -> State# s -> State# s Source #

Prim CRLim 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CRLim -> Int# Source #

alignment# :: CRLim -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CRLim Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CRLim #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CRLim -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CRLim -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CRLim Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CRLim #) Source #

writeOffAddr# :: Addr# -> Int# -> CRLim -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CRLim -> State# s -> State# s Source #

Prim CSpeed 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CSpeed -> Int# Source #

alignment# :: CSpeed -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CSpeed Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CSpeed #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CSpeed -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CSpeed -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CSpeed Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CSpeed #) Source #

writeOffAddr# :: Addr# -> Int# -> CSpeed -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CSpeed -> State# s -> State# s Source #

Prim CSsize 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CSsize -> Int# Source #

alignment# :: CSsize -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CSsize Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CSsize #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CSsize -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CSsize -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CSsize Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CSsize #) Source #

writeOffAddr# :: Addr# -> Int# -> CSsize -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CSsize -> State# s -> State# s Source #

Prim CTcflag 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CTcflag -> Int# Source #

alignment# :: CTcflag -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CTcflag Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CTcflag #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CTcflag -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CTcflag -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CTcflag Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CTcflag #) Source #

writeOffAddr# :: Addr# -> Int# -> CTcflag -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CTcflag -> State# s -> State# s Source #

Prim CTimer 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CTimer -> Int# Source #

alignment# :: CTimer -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CTimer Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CTimer #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CTimer -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CTimer -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CTimer Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CTimer #) Source #

writeOffAddr# :: Addr# -> Int# -> CTimer -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CTimer -> State# s -> State# s Source #

Prim CUid 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: CUid -> Int# Source #

alignment# :: CUid -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> CUid Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CUid #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> CUid -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CUid -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> CUid Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CUid #) Source #

writeOffAddr# :: Addr# -> Int# -> CUid -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> CUid -> State# s -> State# s Source #

Prim Fd 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: Fd -> Int# Source #

alignment# :: Fd -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> Fd Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Fd #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> Fd -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Fd -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> Fd Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Fd #) Source #

writeOffAddr# :: Addr# -> Int# -> Fd -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> Fd -> State# s -> State# s Source #

Prim (StablePtr a) 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: StablePtr a -> Int# Source #

alignment# :: StablePtr a -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> StablePtr a Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, StablePtr a #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> StablePtr a -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> StablePtr a -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> StablePtr a Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, StablePtr a #) Source #

writeOffAddr# :: Addr# -> Int# -> StablePtr a -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> StablePtr a -> State# s -> State# s Source #

Prim (Ptr a) 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: Ptr a -> Int# Source #

alignment# :: Ptr a -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> Ptr a Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Ptr a #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> Ptr a -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Ptr a -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> Ptr a Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Ptr a #) Source #

writeOffAddr# :: Addr# -> Int# -> Ptr a -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> Ptr a -> State# s -> State# s Source #

Prim (FunPtr a) 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: FunPtr a -> Int# Source #

alignment# :: FunPtr a -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> FunPtr a Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, FunPtr a #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> FunPtr a -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> FunPtr a -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> FunPtr a Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, FunPtr a #) Source #

writeOffAddr# :: Addr# -> Int# -> FunPtr a -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> FunPtr a -> State# s -> State# s Source #

Prim a => Prim (Identity a)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: Identity a -> Int# Source #

alignment# :: Identity a -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> Identity a Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Identity a #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> Identity a -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Identity a -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> Identity a Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Identity a #) Source #

writeOffAddr# :: Addr# -> Int# -> Identity a -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> Identity a -> State# s -> State# s Source #

Prim a => Prim (Dual a)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: Dual a -> Int# Source #

alignment# :: Dual a -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> Dual a Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Dual a #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> Dual a -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Dual a -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> Dual a Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Dual a #) Source #

writeOffAddr# :: Addr# -> Int# -> Dual a -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> Dual a -> State# s -> State# s Source #

Prim a => Prim (Product a)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: Product a -> Int# Source #

alignment# :: Product a -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> Product a Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Product a #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> Product a -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Product a -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> Product a Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Product a #) Source #

writeOffAddr# :: Addr# -> Int# -> Product a -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> Product a -> State# s -> State# s Source #

Prim a => Prim (Sum a)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: Sum a -> Int# Source #

alignment# :: Sum a -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> Sum a Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Sum a #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> Sum a -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Sum a -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> Sum a Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Sum a #) Source #

writeOffAddr# :: Addr# -> Int# -> Sum a -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> Sum a -> State# s -> State# s Source #

Prim a => Prim (Down a)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: Down a -> Int# Source #

alignment# :: Down a -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> Down a Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Down a #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> Down a -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Down a -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> Down a Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Down a #) Source #

writeOffAddr# :: Addr# -> Int# -> Down a -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> Down a -> State# s -> State# s Source #

Prim a => Prim (First a)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: First a -> Int# Source #

alignment# :: First a -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> First a Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, First a #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> First a -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> First a -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> First a Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, First a #) Source #

writeOffAddr# :: Addr# -> Int# -> First a -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> First a -> State# s -> State# s Source #

Prim a => Prim (Last a)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: Last a -> Int# Source #

alignment# :: Last a -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> Last a Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Last a #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> Last a -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Last a -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> Last a Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Last a #) Source #

writeOffAddr# :: Addr# -> Int# -> Last a -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> Last a -> State# s -> State# s Source #

Prim a => Prim (Max a)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: Max a -> Int# Source #

alignment# :: Max a -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> Max a Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Max a #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> Max a -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Max a -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> Max a Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Max a #) Source #

writeOffAddr# :: Addr# -> Int# -> Max a -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> Max a -> State# s -> State# s Source #

Prim a => Prim (Min a)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: Min a -> Int# Source #

alignment# :: Min a -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> Min a Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Min a #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> Min a -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Min a -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> Min a Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Min a #) Source #

writeOffAddr# :: Addr# -> Int# -> Min a -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> Min a -> State# s -> State# s Source #

Prim a => Prim (Const a b)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: Const a b -> Int# Source #

alignment# :: Const a b -> Int# Source #

indexByteArray# :: ByteArray# -> Int# -> Const a b Source #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Const a b #) Source #

writeByteArray# :: MutableByteArray# s -> Int# -> Const a b -> State# s -> State# s Source #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Const a b -> State# s -> State# s Source #

indexOffAddr# :: Addr# -> Int# -> Const a b Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Const a b #) Source #

writeOffAddr# :: Addr# -> Int# -> Const a b -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> Const a b -> State# s -> State# s Source #

Accessors

Length information

length :: Prim a => MVector s a -> Int Source #

Length of the mutable vector.

null :: Prim a => MVector s a -> Bool Source #

Check whether the vector is empty

Extracting subvectors

slice Source #

Arguments

:: Prim a 
=> Int

i starting index

-> Int

n length

-> MVector s a 
-> MVector s a 

Yield a part of the mutable vector without copying it. The vector must contain at least i+n elements.

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

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

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

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

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

unsafeSlice Source #

Arguments

:: Prim a 
=> Int

starting index

-> Int

length of the slice

-> MVector s a 
-> MVector s a 

Yield a part of the mutable vector without copying it. No bounds checks are performed.

unsafeInit :: Prim a => MVector s a -> MVector s a Source #

unsafeTail :: Prim a => MVector s a -> MVector s a Source #

unsafeTake :: Prim a => Int -> MVector s a -> MVector s a Source #

unsafeDrop :: Prim a => Int -> MVector s a -> MVector s a Source #

Overlapping

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

Check whether two vectors overlap.

Construction

Initialisation

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

Create a mutable vector of the given length.

unsafeNew :: (PrimMonad m, Prim a) => Int -> m (MVector (PrimState m) a) Source #

Create a mutable vector of the given length. The memory is not initialized.

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

Create a mutable vector of the given length (0 if the length is negative) and fill it with an initial value.

replicateM :: (PrimMonad m, Prim a) => Int -> m a -> m (MVector (PrimState m) a) Source #

Create a mutable vector of the given length (0 if the length is negative) and fill it with values produced by repeatedly executing the monadic action.

clone :: (PrimMonad m, Prim a) => MVector (PrimState m) a -> m (MVector (PrimState m) a) Source #

Create a copy of a mutable vector.

Growing

grow :: (PrimMonad m, Prim a) => MVector (PrimState m) a -> Int -> m (MVector (PrimState m) a) Source #

Grow a vector by the given number of elements. The number must be positive.

unsafeGrow :: (PrimMonad m, Prim a) => MVector (PrimState m) a -> Int -> m (MVector (PrimState m) a) Source #

Grow a vector by the given number of elements. The number must be positive but this is not checked.

Restricting memory usage

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

Reset all elements of the vector to some undefined value, clearing all references to external objects. This is usually a noop for unboxed vectors.

Accessing individual elements

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

Yield the element at the given position.

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

Replace the element at the given position.

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

Modify the element at the given position.

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

Swap the elements at the given positions.

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

Yield the element at the given position. No bounds checks are performed.

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

Replace the element at the given position. No bounds checks are performed.

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

Modify the element at the given position. No bounds checks are performed.

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

Swap the elements at the given positions. No bounds checks are performed.

Modifying vectors

nextPermutation :: (PrimMonad m, Ord e, Prim e) => MVector (PrimState m) e -> m Bool Source #

Compute the next (lexicographically) permutation of given vector in-place. Returns False when input is the last permutation

Filling and copying

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

Set all elements of the vector to the given value.

copy Source #

Arguments

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

target

-> MVector (PrimState m) a

source

-> m () 

Copy a vector. The two vectors must have the same length and may not overlap.

move Source #

Arguments

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

target

-> MVector (PrimState m) a

source

-> m () 

Move the contents of a vector. The two vectors must have the same length.

If the vectors do not overlap, then this is equivalent to copy. Otherwise, the copying is performed as if the source vector were copied to a temporary vector and then the temporary vector was copied to the target vector.

unsafeCopy Source #

Arguments

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

target

-> MVector (PrimState m) a

source

-> m () 

Copy a vector. The two vectors must have the same length and may not overlap. This is not checked.

unsafeMove Source #

Arguments

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

target

-> MVector (PrimState m) a

source

-> m () 

Move the contents of a vector. The two vectors must have the same length, but this is not checked.

If the vectors do not overlap, then this is equivalent to unsafeCopy. Otherwise, the copying is performed as if the source vector were copied to a temporary vector and then the temporary vector was copied to the target vector.