primitive-0.2.1: Wrappers for primitive operations

Portabilitynon-portable
MaintainerRoman Leshchinskiy <rl@cse.unsw.edu.au>

Control.Monad.Primitive

Description

Primitive state-transformer monads

Synopsis

Documentation

class Monad m => PrimMonad m whereSource

Class of primitive state-transformer monads

Associated Types

type PrimState m Source

State token type

Methods

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

Execute a primitive operation

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

Expose the internal structure of the monad

Instances

data RealWorld

RealWorld is deeply magical. It is primitive, but it is not unlifted (hence ptrArg). We never manipulate values of type RealWorld; it's only used in the type system, to parameterise State#.

primitive_ :: PrimMonad m => (State# (PrimState m) -> State# (PrimState m)) -> m ()Source

Execute a primitive operation with no result

primToPrim :: (PrimMonad m1, PrimMonad m2, PrimState m1 ~ PrimState m2) => m1 a -> m2 aSource

Convert a PrimMonad to another monad with the same state token.

primToIO :: (PrimMonad m, PrimState m ~ RealWorld) => m a -> IO aSource

Convert a PrimMonad with a RealWorld state token to IO

primToST :: PrimMonad m => m a -> ST (PrimState m) aSource

Convert a PrimMonad to ST

unsafePrimToPrim :: (PrimMonad m1, PrimMonad m2) => m1 a -> m2 aSource

Convert a PrimMonad to another monad with a possibly different state token. This operation is highly unsafe!

unsafePrimToIO :: PrimMonad m => m a -> IO aSource

Convert any PrimMonad to IO. This operation is highly unsafe!

unsafePrimToST :: PrimMonad m => m a -> ST s aSource

Convert any PrimMonad to ST with an arbitrary state token. This operations is highly unsafe!