| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Control.Monad.HashCons
Contents
Description
Provides a transformer, and a capability type class in the style of mtl,
for hash consing. See the Covenant wiki for how this works.
Synopsis
- data HashConsT r e (m :: Type -> Type) a
- runHashConsT :: HashConsT r e m a -> m (a, Bimap r e)
- hashCons :: forall r e (m :: Type -> Type). (Ord r, Ord e, Bounded r, Enum r, Monad m) => e -> HashConsT r e m r
- lookupRef_ :: forall r e (m :: Type -> Type). (Monad m, Ord e, Ord r) => r -> HashConsT r e m (Maybe e)
- class (Eq e, Eq r, Monad m) => MonadHashCons r e (m :: Type -> Type) | m -> e r where
Transformer
data HashConsT r e (m :: Type -> Type) a Source #
A transformer implementing hash consing capabilities, with references of
type r and referents of type e. It is assumed that values of type e
contain values of type r in their capacity as references, though this is
not a requirement of this transformer.
Important note
This implementation is not suitable for any m that throws exceptions. This
includes IO, ST and anything stacked atop them. For the reasons why, see
here.
Since: 1.0.0
Instances
| (Ord r, Ord e, Bounded r, Enum r, Monad m) => MonadHashCons r e (HashConsT r e m) Source # | Since: 1.0.0 |
| MonadTrans (HashConsT r e) Source # | Since: 1.0.0 |
Defined in Control.Monad.HashCons | |
| Monad m => Applicative (HashConsT r e m) Source # | Since: 1.0.0 |
Defined in Control.Monad.HashCons Methods pure :: a -> HashConsT r e m a # (<*>) :: HashConsT r e m (a -> b) -> HashConsT r e m a -> HashConsT r e m b # liftA2 :: (a -> b -> c) -> HashConsT r e m a -> HashConsT r e m b -> HashConsT r e m c # (*>) :: HashConsT r e m a -> HashConsT r e m b -> HashConsT r e m b # (<*) :: HashConsT r e m a -> HashConsT r e m b -> HashConsT r e m a # | |
| Functor m => Functor (HashConsT r e m) Source # | Since: 1.0.0 |
| Monad m => Monad (HashConsT r e m) Source # | Since: 1.0.0 |
runHashConsT :: HashConsT r e m a -> m (a, Bimap r e) Source #
Execute the computation described, returning both the result and the unique
pairings of r and e produced as part of it.
Since: 1.0.0
hashCons :: forall r e (m :: Type -> Type). (Ord r, Ord e, Bounded r, Enum r, Monad m) => e -> HashConsT r e m r Source #
Given a value of type e, produce the unique value of type r acting as a
reference to it. This r will be cached, ensuring any future requests for
the reference for this value of type e will be the same.
Since: 1.0.0
lookupRef_ :: forall r e (m :: Type -> Type). (Monad m, Ord e, Ord r) => r -> HashConsT r e m (Maybe e) Source #
Given a value of type r, fetch the cached e value, if it exists.
Since: 1.0.0
Capability type class
class (Eq e, Eq r, Monad m) => MonadHashCons r e (m :: Type -> Type) | m -> e r where Source #
An mtl-style capability type class for hash consing capability, using
references of type r and values of type e.
Laws
refTox>>refTox=refToxliftA2(/=) (refTox) (refToy)=refTox*>refToy*>pure(x/=y)refTox>>=(\r ->lookupRefr>>=(\y ->pure(y, r)))=(Justx, )<$>refTox
Since: 1.0.0
Methods
Produce the unique value of type r that acts as a reference for the
given value of type e.
Since: 1.0.0
lookupRef :: r -> m (Maybe e) Source #
Given a value of type r, fetch the cached value of type e.
Since: 1.0.0
Instances
| MonadHashCons Id ASGNode ASGBuilder Source # | Since: 1.0.0 |
Defined in Covenant.ASG | |
| MonadHashCons Id ASGNode DebugASGBuilder Source # | Since: 1.0.0 |
Defined in Covenant.Test | |
| (Ord r, Ord e, MonadHashCons r e m) => MonadHashCons r e (MaybeT m) Source # | Since: 1.0.0 |
| MonadHashCons r e m => MonadHashCons r e (ExceptT e' m) Source # | Since: 1.0.0 |
| MonadHashCons r e m => MonadHashCons r e (ReaderT r' m) Source # | Since: 1.0.0 |
| MonadHashCons r e m => MonadHashCons r e (StateT s m) Source # | Since: 1.0.0 |
| MonadHashCons r e m => MonadHashCons r e (WriterT w m) Source # | Since: 1.0.0 |
| (Ord r, Ord e, Bounded r, Enum r, Monad m) => MonadHashCons r e (HashConsT r e m) Source # | Since: 1.0.0 |
| MonadHashCons r e m => MonadHashCons r e (RWST r' w s m) Source # | Since: 1.0.0 |