| Safe Haskell | None |
|---|
Control.Monad.Atom
Description
The Atom monad provides functions which convert objects to unique atoms (represented as Ints). Example:
example = evalAtom $ do xs <- mapM toAtom "abcabd" zs <- mapM fromAtom xs return $ zip zs xs
>>>example>>>[('a',0),('b',1),('c',2),('a',0),('b',1),('d',3)]
- data AtomTable a
- data Atom a r
- data AtomT a m r
- toAtom :: MonadAtom m => Key m -> m Int
- fromAtom :: MonadAtom m => Int -> m (Key m)
- maybeToAtom :: MonadAtom m => Key m -> m (Maybe Int)
- empty :: Ord a => AtomTable a
- evalAtom :: Ord a => Atom a r -> r
- evalAtomT :: (Ord a, Monad m) => AtomT a m r -> m r
- runAtom :: Ord a => Atom a r -> AtomTable a -> (r, AtomTable a)
- runAtomT :: (Ord a, Monad m) => AtomT a m r -> AtomTable a -> m (r, AtomTable a)
- mapping :: Ord a => AtomTable a -> Map a Int
Documentation
AtomTable holds the state necessary for converting to and from
Ints.
Atom is a specialized state monad for converting to and from
Ints.
AtomT is a specialized state monad transformer for converting
to and from Ints.
fromAtom :: MonadAtom m => Int -> m (Key m)Source
fromAtom i converts the Int i to its corresponding object
in the Atom monad.
maybeToAtom :: MonadAtom m => Key m -> m (Maybe Int)Source
maybeToAtom x converts x to a unique Int in the Atom
monad only if x already has a corresponding Int
evalAtom :: Ord a => Atom a r -> rSource
evalAtom c runs computation c in the Atom monad with the empty
initial AtomTable.
evalAtomT :: (Ord a, Monad m) => AtomT a m r -> m rSource
evalAtomT c runs computation c in the AtomT monad transformer
with the empty initial AtomTable.
runAtom :: Ord a => Atom a r -> AtomTable a -> (r, AtomTable a)Source
runAtom c s runs computation c in the Atom monad with the
initial AtomTable s.