Z-Data-1.0.0.0: Array, vector and text
Copyright(c) Dong Han 2017~2019
LicenseBSD-style
Maintainerwinterland1989@gmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Z.Data.PrimRef

Description

This package provide fast primitive references for primitive monad, such as ST or IO. Unboxed reference is implemented using single cell MutableByteArray/MutableUnliftedArray s to eliminate indirection overhead which MutVar# s a carry, on the otherhand primitive reference only support limited type(instances of 'Prim/PrimUnlifted' class).

Synopsis

Prim references

newtype PrimRef s a Source #

A mutable variable in the PrimMonad which can hold an instance of Prim.

Constructors

PrimRef (MutableByteArray s) 

type PrimIORef a = PrimRef RealWorld a Source #

Type alias for PrimRef in IO.

newPrimRef :: (Prim a, PrimMonad m) => a -> m (PrimRef (PrimState m) a) Source #

Build a new PrimRef

readPrimRef :: (Prim a, PrimMonad m) => PrimRef (PrimState m) a -> m a Source #

Read the value of an PrimRef

writePrimRef :: (Prim a, PrimMonad m) => PrimRef (PrimState m) a -> a -> m () Source #

Write a new value into an PrimRef

modifyPrimRef :: (Prim a, PrimMonad m) => PrimRef (PrimState m) a -> (a -> a) -> m () Source #

Mutate the contents of an PrimRef.

Unboxed reference is always strict on the value it hold.

class Prim a where #

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.

Methods

sizeOf# :: a -> Int# #

Size of values of type a. The argument is not used.

alignment# :: a -> Int# #

Alignment of values of type a. The argument is not used.

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

Read a value from the array. The offset is in elements of type a rather than in bytes.

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

Read a value from the mutable array. The offset is in elements of type a rather than in bytes.

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

Write a value to the mutable array. The offset is in elements of type a rather than in bytes.

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

Fill a slice of the mutable array with a value. The offset and length of the chunk are in elements of type a rather than in bytes.

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

Read a value from a memory position given by an address and an offset. The memory block the address refers to must be immutable. The offset is in elements of type a rather than in bytes.

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

Read a value from a memory position given by an address and an offset. The offset is in elements of type a rather than in bytes.

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

Write a value to a memory position given by an address and an offset. The offset is in elements of type a rather than in bytes.

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

Fill a memory block given by an address, an offset and a length. The offset and length are in elements of type a rather than in bytes.

Instances

Instances details
Prim Char 
Instance details

Defined in Data.Primitive.Types

Prim Double 
Instance details

Defined in Data.Primitive.Types

Prim Float 
Instance details

Defined in Data.Primitive.Types

Prim Int 
Instance details

Defined in Data.Primitive.Types

Prim Int8 
Instance details

Defined in Data.Primitive.Types

Prim Int16 
Instance details

Defined in Data.Primitive.Types

Prim Int32 
Instance details

Defined in Data.Primitive.Types

Prim Int64 
Instance details

Defined in Data.Primitive.Types

Prim Word 
Instance details

Defined in Data.Primitive.Types

Prim Word8 
Instance details

Defined in Data.Primitive.Types

Prim Word16 
Instance details

Defined in Data.Primitive.Types

Prim Word32 
Instance details

Defined in Data.Primitive.Types

Prim Word64 
Instance details

Defined in Data.Primitive.Types

Prim CDev 
Instance details

Defined in Data.Primitive.Types

Prim CIno 
Instance details

Defined in Data.Primitive.Types

Prim CMode 
Instance details

Defined in Data.Primitive.Types

Prim COff 
Instance details

Defined in Data.Primitive.Types

Prim CPid 
Instance details

Defined in Data.Primitive.Types

Prim CSsize 
Instance details

Defined in Data.Primitive.Types

Prim CGid 
Instance details

Defined in Data.Primitive.Types

Prim CNlink 
Instance details

Defined in Data.Primitive.Types

Prim CUid 
Instance details

Defined in Data.Primitive.Types

Prim CCc 
Instance details

Defined in Data.Primitive.Types

Prim CSpeed 
Instance details

Defined in Data.Primitive.Types

Prim CTcflag 
Instance details

Defined in Data.Primitive.Types

Prim CRLim 
Instance details

Defined in Data.Primitive.Types

Prim CBlkSize 
Instance details

Defined in Data.Primitive.Types

Prim CBlkCnt 
Instance details

Defined in Data.Primitive.Types

Prim CClockId 
Instance details

Defined in Data.Primitive.Types

Prim CFsBlkCnt 
Instance details

Defined in Data.Primitive.Types

Prim CFsFilCnt 
Instance details

Defined in Data.Primitive.Types

Prim CId 
Instance details

Defined in Data.Primitive.Types

Prim CKey 
Instance details

Defined in Data.Primitive.Types

Prim CTimer 
Instance details

Defined in Data.Primitive.Types

Prim Fd 
Instance details

Defined in Data.Primitive.Types

Prim CChar 
Instance details

Defined in Data.Primitive.Types

Prim CSChar 
Instance details

Defined in Data.Primitive.Types

Prim CUChar 
Instance details

Defined in Data.Primitive.Types

Prim CShort 
Instance details

Defined in Data.Primitive.Types

Prim CUShort 
Instance details

Defined in Data.Primitive.Types

Prim CInt 
Instance details

Defined in Data.Primitive.Types

Prim CUInt 
Instance details

Defined in Data.Primitive.Types

Prim CLong 
Instance details

Defined in Data.Primitive.Types

Prim CULong 
Instance details

Defined in Data.Primitive.Types

Prim CLLong 
Instance details

Defined in Data.Primitive.Types

Prim CULLong 
Instance details

Defined in Data.Primitive.Types

Prim CBool 
Instance details

Defined in Data.Primitive.Types

Prim CFloat 
Instance details

Defined in Data.Primitive.Types

Prim CDouble 
Instance details

Defined in Data.Primitive.Types

Prim CPtrdiff 
Instance details

Defined in Data.Primitive.Types

Prim CSize 
Instance details

Defined in Data.Primitive.Types

Prim CWchar 
Instance details

Defined in Data.Primitive.Types

Prim CSigAtomic 
Instance details

Defined in Data.Primitive.Types

Prim CClock 
Instance details

Defined in Data.Primitive.Types

Prim CTime 
Instance details

Defined in Data.Primitive.Types

Prim CUSeconds 
Instance details

Defined in Data.Primitive.Types

Prim CSUSeconds 
Instance details

Defined in Data.Primitive.Types

Prim CIntPtr 
Instance details

Defined in Data.Primitive.Types

Prim CUIntPtr 
Instance details

Defined in Data.Primitive.Types

Prim CIntMax 
Instance details

Defined in Data.Primitive.Types

Prim CUIntMax 
Instance details

Defined in Data.Primitive.Types

Prim WordPtr

Since: primitive-0.7.1.0

Instance details

Defined in Data.Primitive.Types

Prim IntPtr

Since: primitive-0.7.1.0

Instance details

Defined in Data.Primitive.Types

Prim (StablePtr a) 
Instance details

Defined in Data.Primitive.Types

Prim (Ptr a) 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: Ptr a -> Int# #

alignment# :: Ptr a -> Int# #

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

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

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

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

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

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

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

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

Prim (FunPtr a) 
Instance details

Defined in Data.Primitive.Types

Prim a => Prim (Min a)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: Min a -> Int# #

alignment# :: Min a -> Int# #

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

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

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

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

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

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

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

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

Prim a => Prim (Max a)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: Max a -> Int# #

alignment# :: Max a -> Int# #

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

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

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

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

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

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

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

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

Prim a => Prim (First a)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Prim a => Prim (Last a)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Prim a => Prim (Identity a)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Prim a => Prim (Dual a)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Prim a => Prim (Sum a)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: Sum a -> Int# #

alignment# :: Sum a -> Int# #

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

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

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

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

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

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

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

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

Prim a => Prim (Product a)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Prim a => Prim (Down a)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Prim a => Prim (RadixDown a) Source # 
Instance details

Defined in Z.Data.Vector.Sort

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# #

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

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

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

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

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

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

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

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

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

Unlifted references

newtype UnliftedRef s a Source #

A mutable variable in the PrimMonad which can hold an instance of PrimUnlifted.

Constructors

UnliftedRef (MutableUnliftedArray s a) 

readUnliftedRef :: (PrimUnlifted a, PrimMonad m) => UnliftedRef (PrimState m) a -> m a Source #

Read the value of an UnliftedRef

writeUnliftedRef :: (PrimUnlifted a, PrimMonad m) => UnliftedRef (PrimState m) a -> a -> m () Source #

Write a new value into an UnliftedRef

modifyUnliftedRef :: (PrimUnlifted a, PrimMonad m) => UnliftedRef (PrimState m) a -> (a -> a) -> m () Source #

Mutate the contents of an UnliftedRef.

Unlifted reference is always strict on the value it hold.

class PrimUnlifted a where Source #

Types with TYPE UnliftedRep, which can be stored / retrieved in ArrayArray#.

Instances

Instances details
PrimUnlifted ByteArray Source # 
Instance details

Defined in Z.Data.Array.UnliftedArray

PrimUnlifted (TVar a) Source # 
Instance details

Defined in Z.Data.Array.UnliftedArray

PrimUnlifted (IORef a) Source # 
Instance details

Defined in Z.Data.Array.UnliftedArray

PrimUnlifted (MVar a) Source # 
Instance details

Defined in Z.Data.Array.UnliftedArray

PrimUnlifted (PrimArray a) Source # 
Instance details

Defined in Z.Data.Array.UnliftedArray

PrimUnlifted (MutableByteArray s) Source # 
Instance details

Defined in Z.Data.Array.UnliftedArray

PrimUnlifted (STRef s a) Source # 
Instance details

Defined in Z.Data.Array.UnliftedArray

PrimUnlifted (MutablePrimArray s a) Source # 
Instance details

Defined in Z.Data.Array.UnliftedArray

Atomic operations for PrimIORef Int

type Counter = PrimRef RealWorld Int Source #

Alias for 'PrimIORef Int' which support several atomic operations.

readCounter :: Counter -> IO Int Source #

Read the value of an Counter.

writeCounter :: Counter -> Int -> IO () Source #

Write a new value into an Counter(non-atomically).

modifyCounter :: Counter -> (Int -> Int) -> IO () Source #

Mutate the contents of an Counter(non-atomically).

return value BEFORE atomic operation

atomicAddCounter :: Counter -> Int -> IO Int Source #

Atomically add a Counter, return the value BEFORE added.

atomicSubCounter :: Counter -> Int -> IO Int Source #

Atomically sub a Counter, return the value BEFORE subbed.

atomicAndCounter :: Counter -> Int -> IO Int Source #

Atomically and a Counter, return the value BEFORE anded.

atomicNandCounter :: Counter -> Int -> IO Int Source #

Atomically nand a Counter, return the value BEFORE nanded.

atomicOrCounter :: Counter -> Int -> IO Int Source #

Atomically or a Counter, return the value BEFORE ored.

atomicXorCounter :: Counter -> Int -> IO Int Source #

Atomically xor a Counter, return the value BEFORE xored.

return value AFTER atomic operation

atomicAddCounter' :: Counter -> Int -> IO Int Source #

Atomically add a Counter, return the value AFTER added.

atomicSubCounter' :: Counter -> Int -> IO Int Source #

Atomically sub a Counter, return the value AFTER subbed.

atomicAndCounter' :: Counter -> Int -> IO Int Source #

Atomically and a Counter, return the value AFTER anded.

atomicNandCounter' :: Counter -> Int -> IO Int Source #

Atomically nand a Counter, return the value AFTER nanded.

atomicOrCounter' :: Counter -> Int -> IO Int Source #

Atomically or a Counter, return the value AFTER ored.

atomicXorCounter' :: Counter -> Int -> IO Int Source #

Atomically xor a Counter, return the value AFTER xored.

without returning

atomicAddCounter_ :: Counter -> Int -> IO () Source #

Atomically add a Counter.

atomicSubCounter_ :: Counter -> Int -> IO () Source #

Atomically sub a Counter

atomicAndCounter_ :: Counter -> Int -> IO () Source #

Atomically and a Counter

atomicNandCounter_ :: Counter -> Int -> IO () Source #

Atomically nand a Counter

atomicOrCounter_ :: Counter -> Int -> IO () Source #

Atomically or a Counter

atomicXorCounter_ :: Counter -> Int -> IO () Source #

Atomically xor a Counter