foundation-0.0.3: Alternative prelude with batteries and no dependencies

LicenseBSD-style
MaintainerVincent Hanquez <vincent@snarc.org>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Foundation.Primitive

Description

Different collections (list, vector, string, ..) unified under 1 API. an API to rules them all, and in the darkness bind them.

Synopsis

Documentation

class Eq ty => PrimType ty where Source #

Represent the accessor for types that can be stored in the UArray and MUArray.

Types need to be a instance of storable and have fixed sized.

Methods

primSizeInBytes :: Proxy ty -> Size8 Source #

get the size in bytes of a ty element

primBaUIndex :: ByteArray# -> Offset ty -> ty Source #

return the element stored at a specific index

primMbaURead :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset ty -> prim ty Source #

Read an element at an index in a mutable array

primMbaUWrite :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset ty -> ty -> prim () Source #

Write an element to a specific cell in a mutable array.

primAddrIndex :: Addr# -> Offset ty -> ty Source #

Read from Address, without a state. the value read should be considered a constant for all pratical purpose, otherwise bad thing will happens.

primAddrRead :: PrimMonad prim => Addr# -> Offset ty -> prim ty Source #

Read a value from Addr in a specific primitive monad

primAddrWrite :: PrimMonad prim => Addr# -> Offset ty -> ty -> prim () Source #

Write a value to Addr in a specific primitive monad

Instances

PrimType Char Source # 
PrimType Double Source # 
PrimType Float Source # 
PrimType Int8 Source # 
PrimType Int16 Source # 
PrimType Int32 Source # 
PrimType Int64 Source # 
PrimType Word8 Source # 
PrimType Word16 Source # 
PrimType Word32 Source # 
PrimType Word64 Source # 
PrimType CChar Source # 
PrimType CUChar Source # 

class (Functor m, Monad m) => PrimMonad m where Source #

Primitive monad that can handle mutation.

For example: IO and ST.

Associated Types

type PrimState m Source #

type of state token associated with the PrimMonad m

type PrimVar m :: * -> * Source #

type of variable associated with the PrimMonad m

Methods

primitive :: (State# (PrimState m) -> (#State# (PrimState m), a#)) -> m a Source #

Unwrap the State# token to pass to a function a primitive function that returns an unboxed state and a value.

primThrow :: Exception e => e -> m a Source #

Throw Exception in the primitive monad

unPrimMonad :: m a -> State# (PrimState m) -> (#State# (PrimState m), a#) Source #

Run a Prim monad from a dedicated state#

primVarNew :: a -> m (PrimVar m a) Source #

Build a new variable in the Prim Monad

primVarRead :: PrimVar m a -> m a Source #

Read the variable in the Prim Monad

primVarWrite :: PrimVar m a -> a -> m () Source #

Write the variable in the Prim Monad

Instances

PrimMonad IO Source # 

Associated Types

type PrimState (IO :: * -> *) :: * Source #

type PrimVar (IO :: * -> *) :: * -> * Source #

PrimMonad (ST s) Source # 

Associated Types

type PrimState (ST s :: * -> *) :: * Source #

type PrimVar (ST s :: * -> *) :: * -> * Source #

Methods

primitive :: (State# (PrimState (ST s)) -> (#VoidRep, PtrRepLifted, State# (PrimState (ST s)), a#)) -> ST s a Source #

primThrow :: Exception e => e -> ST s a Source #

unPrimMonad :: ST s a -> State# (PrimState (ST s)) -> (#VoidRep, PtrRepLifted, State# (PrimState (ST s)), a#) Source #

primVarNew :: a -> ST s (PrimVar (ST s) a) Source #

primVarRead :: PrimVar (ST s) a -> ST s a Source #

primVarWrite :: PrimVar (ST s) a -> a -> ST s () Source #