antisplice-0.12.1.0: An engine for text-based dungeons.

Safe HaskellNone

Game.Antisplice.Utils.Atoms

Description

Provides a variable-storing monad and functions for access (they almost form an arrow)

Synopsis

Documentation

newtype Atom a Source

Phantom type for atom IDs

Constructors

Atom Int 

Instances

Eq (Atom a) 
Ord (Atom a) 

newtype AtomStoreT m a Source

The storage monad

Constructors

AtomStore 

Fields

runAtomStoreT :: AVL (Int, Dynamic) -> m (a, AVL (Int, Dynamic))
 

Instances

MonadTrans AtomStoreT 
MonadError SplErr m0 => MonadError SplErr (AtomStoreT m0) 
ChannelPrinter Bool m0 => ChannelPrinter Bool (AtomStoreT m0) 
ChannelPrinter Int m0 => ChannelPrinter Int (AtomStoreT m0) 
ChannelPrinter Handle m0 => ChannelPrinter Handle (AtomStoreT m0) 
ChannelPrinter PlayerId m0 => ChannelPrinter PlayerId (AtomStoreT m0) 
(MonadDungeon m0, ChannelPrinter PlayerId m0) => Broadcaster PlayerId (AtomStoreT m0) 
Monad m => Monad (AtomStoreT m) 
Functor m => Functor (AtomStoreT m) 
MonadIO m => MonadIO (AtomStoreT m) 
MonadCounter m => MonadCounter (AtomStoreT m) 
(Functor m, MonadCounter m) => MonadAtoms (AtomStoreT m) 
MonadVocab m0 => MonadVocab (AtomStoreT m0) 
MonadPrinter m0 => MonadPrinter (AtomStoreT m0) 
MonadFinalizer m0 => MonadFinalizer (AtomStoreT m0) 
MonadScanner m0 => MonadScanner (AtomStoreT m0) 
MonadExpand m0 => MonadExpand (AtomStoreT m0) 
ExpanderEnv m0 => ExpanderEnv (AtomStoreT m0) 
MonadRandom m0 => MonadRandom (AtomStoreT m0) 
MonadClock m0 => MonadClock (AtomStoreT m0) 
ExtendedPrinter m0 => ExtendedPrinter (AtomStoreT m0) 
MonadDungeon m0 => MonadDungeon (AtomStoreT m0) 
MonadPlayer m0 => MonadPlayer (AtomStoreT m0) 
MonadRoom m0 => MonadRoom (AtomStoreT m0) 
MonadSpawn m0 => MonadSpawn (AtomStoreT m0) 
HistoryEnv m0 => HistoryEnv (AtomStoreT m0) 

class MonadCounter m => MonadAtoms m whereSource

Typeclass for all atom-storing monads.

Methods

newAtom :: Typeable v => m (Atom v)Source

Reserve a new atom.

putAtom :: Typeable v => Atom v -> v -> m ()Source

Save a value for the given atom.

getAtom :: Typeable v => Atom v -> m vSource

Get the value from a given atom.

dispAtom :: Atom v -> m ()Source

Dispose the given atom.

cloneAtom :: Typeable v => Atom v -> m (Atom v)Source

Clone the given atom.

newtype (Typeable a, Typeable b) => Atomar m a b Source

Atomar operation (almost arrow)

Constructors

Atomar 

Fields

runAtomar :: Atom a -> m (Atom b)
 

mapAtom :: (Typeable a, Typeable b, MonadAtoms m) => (a -> b) -> Atom a -> m (Atom b)Source

Run a pure function on atoms.