mzv-0.1.0.2: Implementation of the "Monads, Zippers and Views" (Schrijvers and Oliveira, ICFP'11)

Safe HaskellNone

Control.Monad.Mask

Documentation

newtype Tagged tag m a Source

Constructors

Tag 

Fields

unTag :: m a
 

Instances

(LWith list n (:> t t' m), Monad n, Monad m, MonadTrans t, MonadTrans t') => LWith1 list HFalse n (Tagged e (t (t' m))) 
(Monad m, ~ (* -> *) n (t n'), Monad n', LWith list n' m, MonadTrans t) => LWith1 list HTrue n (Tagged e (t m)) 
(Monad m, Monad n, LWith list n (:> (:> t0 t1) t2 m), MonadTrans t2, MonadTrans t1, MonadTrans t0) => LWith2 list HFalse n (:> t0 (Tagged e) (t1 (t2 m))) 
(Monad m, ~ (* -> *) n (:> t0 t n'), Monad n', LWith list n' m, MonadTrans t, MonadTrans t0) => LWith2 list HTrue n (:> t0 (Tagged e) (t m)) 
(HMember t l b, LWith1 l b n (Tagged t m), Monad m, Monad n) => LWith l n (Tagged t m) 
(Monad m, ~ (* -> *) m (t n), MonadTrans t) => TWith tag m (Tagged tag (t n)) 
(Monad m, ~ (* -> *) m n) => TWith tag n (Tagged tag m) 
(HMember t l b, LWith2 l b n (:> t0 (Tagged t) m), Monad m, Monad n) => LWith l n (:> t0 (Tagged t) m) 
(Monad (t' n), Monad m, Monad n, MonadTrans t, ~ (* -> *) m (:> (:> t (Tagged tag)) t' n), MonadTrans t') => TWith tag m (:> t (Tagged tag) (t' n)) 
(Monad m, Monad n, MonadTrans t, ~ (* -> *) m (t n)) => TWith tag m (:> t (Tagged tag) n) 
MonadState s m => MonadState s (Tagged t m) 
MonadTrans (Tagged tag) 
Monad m => Monad (Tagged tag m) 

type TStateT tag s m = Tagged tag (StateT s m)Source

runTStateT :: Monad m => s -> TStateT tag s m a -> m (a, s)Source

evalTStateT :: Monad m => s -> TStateT tag s m a -> m aSource

type TErrorT tag error m = Tagged tag (ErrorT error m)Source

runTErrorT :: Monad m => TErrorT tag e m a -> m (Either e a)Source

class (Monad m, Monad n) => TWith tag n m whereSource

Methods

structure :: View g => tag -> n `g` mSource

Instances

(Monad (t0 (t1 n)), Monad m, Monad n, TWith tag m (:> t0 t1 n), MonadTrans t0, MonadTrans t1) => TWith tag m (t0 (t1 n)) 
(Monad m, ~ (* -> *) m (t n), MonadTrans t) => TWith tag m (Tagged tag (t n)) 
(Monad m, ~ (* -> *) m n) => TWith tag n (Tagged tag m) 
(Monad (t' n), Monad m, Monad n, MonadTrans t, ~ (* -> *) m (:> (:> t (Tagged tag)) t' n), MonadTrans t') => TWith tag m (:> t (Tagged tag) (t' n)) 
(Monad m, Monad n, MonadTrans t, ~ (* -> *) m (t n)) => TWith tag m (:> t (Tagged tag) n) 

use :: TWith tag n m => n a -> tag -> m aSource

expose :: TWith tag n m => m a -> tag -> n aSource

t :: View g => m `g` Tagged tag mSource

unt :: View g => Tagged tag m `g` mSource

inverse_o :: View g => g (t1 (t2 m)) (:> t1 t2 m)Source

data Log1 Source

Constructors

Log1 

data Log2 Source

Constructors

Log2 

ifpos1 :: MonadState Int m => m () -> m ()Source

luse :: LWith taglist n m => n a -> taglist -> m aSource

data e :&: l Source

Constructors

e :&: l 

Instances

HMember e l b => HMember e (:&: f l) b 
~ * b HTrue => HMember e (:&: e l) b 

data HTrue Source

Constructors

HTrue 

Instances

(Monad m, ~ (* -> *) n (t n'), Monad n', LWith list n' m, MonadTrans t) => LWith1 list HTrue n (Tagged e (t m)) 
(Monad m, ~ (* -> *) n (:> t0 t n'), Monad n', LWith list n' m, MonadTrans t, MonadTrans t0) => LWith2 list HTrue n (:> t0 (Tagged e) (t m)) 

data HFalse Source

Constructors

HFalse 

Instances

(LWith list n (:> t t' m), Monad n, Monad m, MonadTrans t, MonadTrans t') => LWith1 list HFalse n (Tagged e (t (t' m))) 
(Monad m, Monad n, LWith list n (:> (:> t0 t1) t2 m), MonadTrans t2, MonadTrans t1, MonadTrans t0) => LWith2 list HFalse n (:> t0 (Tagged e) (t1 (t2 m))) 

class HMember e l b whereSource

Methods

hmember :: e -> l -> bSource

Instances

~ * b HFalse => HMember e f b 
~ * b HTrue => HMember e e b 
HMember e l b => HMember e (:&: f l) b 
~ * b HTrue => HMember e (:&: e l) b 

class LWith list n m whereSource

Methods

lstructure :: View g => list -> n `g` mSource

Instances

(~ (* -> *) m n, Monad m, Monad n) => LWith l n m 
(HMember t l b, LWith1 l b n (Tagged t m), Monad m, Monad n) => LWith l n (Tagged t m) 
(HMember t l b, LWith2 l b n (:> t0 (Tagged t) m), Monad m, Monad n) => LWith l n (:> t0 (Tagged t) m) 

class LWith1 list b n m whereSource

Methods

lstructure1 :: View g => list -> b -> n `g` mSource

Instances

(LWith list n (:> t t' m), Monad n, Monad m, MonadTrans t, MonadTrans t') => LWith1 list HFalse n (Tagged e (t (t' m))) 
(Monad m, ~ (* -> *) n (t n'), Monad n', LWith list n' m, MonadTrans t) => LWith1 list HTrue n (Tagged e (t m)) 

class LWith2 list b n m whereSource

Methods

lstructure2 :: View g => list -> b -> n `g` mSource

Instances

(Monad m, Monad n, LWith list n (:> (:> t0 t1) t2 m), MonadTrans t2, MonadTrans t1, MonadTrans t0) => LWith2 list HFalse n (:> t0 (Tagged e) (t1 (t2 m))) 
(Monad m, ~ (* -> *) n (:> t0 t n'), Monad n', LWith list n' m, MonadTrans t, MonadTrans t0) => LWith2 list HTrue n (:> t0 (Tagged e) (t m)) 

getv :: (Monad m, MonadState a n, MonadMorphism g) => g n m -> m aSource

putv :: (Monad m, MonadState a n, MonadMorphism g) => g n m -> a -> m ()Source