primitive-0.6.1.0: Primitive memory-related operations

Copyright(c) Roman Leshchinskiy 2009
LicenseBSD-style
MaintainerRoman Leshchinskiy <rl@cse.unsw.edu.au>
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Control.Monad.Primitive

Description

Primitive state-transformer monads

Synopsis

Documentation

class Monad m => PrimMonad m where Source

Class of monads which can perform primitive state-transformer actions

Associated Types

type PrimState m Source

State token type

Methods

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

Execute a primitive operation

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

Instances

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

Execute a primitive operation with no result

class PrimMonad m => PrimBase m where Source

Class of primitive monads for state-transformer actions.

Unlike PrimMonad, this typeclass requires that the Monad be fully expressed as a state transformer, therefore disallowing other monad transformers on top of the base IO or ST.

Methods

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

Expose the internal structure of the monad

Instances

liftPrim :: (PrimBase m1, PrimMonad m2, PrimState m1 ~ PrimState m2) => m1 a -> m2 a Source

Lifts a PrimBase into another PrimMonad with the same underlying state token type.

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

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

primToIO :: (PrimBase m, PrimState m ~ RealWorld) => m a -> IO a Source

Convert a PrimBase with a RealWorld state token to IO

primToST :: PrimBase m => m a -> ST (PrimState m) a Source

Convert a PrimBase to ST

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

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

unsafePrimToIO :: PrimBase m => m a -> IO a Source

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

unsafePrimToST :: PrimBase m => m a -> ST s a Source

Convert any PrimBase to ST with an arbitrary state token. This operation is highly unsafe!

touch :: PrimMonad m => a -> m () Source