constraints-0.8: Constraint manipulation

Safe HaskellNone
LanguageHaskell2010

Data.Constraint.Lifting

Documentation

class Lifting p f where Source #

Minimal complete definition

lifting

Methods

lifting :: p a :- p (f a) Source #

Instances

Lifting * Eq [] Source # 

Methods

lifting :: [a] :- [f a] Source #

Lifting * Eq Maybe Source # 

Methods

lifting :: Maybe a :- Maybe (f a) Source #

Lifting * Eq Ratio Source # 

Methods

lifting :: Ratio a :- Ratio (f a) Source #

Lifting * Eq Identity Source # 

Methods

lifting :: Identity a :- Identity (f a) Source #

Lifting * Eq Complex Source # 

Methods

lifting :: Complex a :- Complex (f a) Source #

Lifting * Ord [] Source # 

Methods

lifting :: [a] :- [f a] Source #

Lifting * Ord Maybe Source # 

Methods

lifting :: Maybe a :- Maybe (f a) Source #

Lifting * Ord Identity Source # 

Methods

lifting :: Identity a :- Identity (f a) Source #

Lifting * Read [] Source # 

Methods

lifting :: [a] :- [f a] Source #

Lifting * Read Maybe Source # 

Methods

lifting :: Maybe a :- Maybe (f a) Source #

Lifting * Read Identity Source # 

Methods

lifting :: Identity a :- Identity (f a) Source #

Lifting * Read Complex Source # 

Methods

lifting :: Complex a :- Complex (f a) Source #

Lifting * Show [] Source # 

Methods

lifting :: [a] :- [f a] Source #

Lifting * Show Maybe Source # 

Methods

lifting :: Maybe a :- Maybe (f a) Source #

Lifting * Show Identity Source # 

Methods

lifting :: Identity a :- Identity (f a) Source #

Lifting * Show Complex Source # 

Methods

lifting :: Complex a :- Complex (f a) Source #

Lifting * Monoid Maybe Source # 

Methods

lifting :: Maybe a :- Maybe (f a) Source #

Lifting * Binary [] Source # 

Methods

lifting :: [a] :- [f a] Source #

Lifting * Binary Maybe Source # 

Methods

lifting :: Maybe a :- Maybe (f a) Source #

Lifting * NFData [] Source # 

Methods

lifting :: [a] :- [f a] Source #

Lifting * NFData Maybe Source # 

Methods

lifting :: Maybe a :- Maybe (f a) Source #

Lifting * Hashable [] Source # 

Methods

lifting :: [a] :- [f a] Source #

Lifting * Hashable Maybe Source # 

Methods

lifting :: Maybe a :- Maybe (f a) Source #

Bounded a => Lifting * Bounded ((,) a) Source # 

Methods

lifting :: (a, a) :- (a, f a) Source #

Eq a => Lifting * Eq (Either a) Source # 

Methods

lifting :: Either a a :- Either a (f a) Source #

Eq a => Lifting * Eq ((,) a) Source # 

Methods

lifting :: (a, a) :- (a, f a) Source #

Eq1 m => Lifting * Eq (ListT m) Source # 

Methods

lifting :: ListT m a :- ListT m (f a) Source #

Eq1 f => Lifting * Eq (Lift f) Source # 

Methods

lifting :: Lift f a :- Lift f (f a) Source #

Eq1 m => Lifting * Eq (MaybeT m) Source # 

Methods

lifting :: MaybeT m a :- MaybeT m (f a) Source #

Ord a => Lifting * Ord (Either a) Source # 

Methods

lifting :: Either a a :- Either a (f a) Source #

Ord a => Lifting * Ord ((,) a) Source # 

Methods

lifting :: (a, a) :- (a, f a) Source #

Ord1 m => Lifting * Ord (ListT m) Source # 

Methods

lifting :: ListT m a :- ListT m (f a) Source #

Ord1 f => Lifting * Ord (Lift f) Source # 

Methods

lifting :: Lift f a :- Lift f (f a) Source #

Ord1 m => Lifting * Ord (MaybeT m) Source # 

Methods

lifting :: MaybeT m a :- MaybeT m (f a) Source #

Read a => Lifting * Read (Either a) Source # 

Methods

lifting :: Either a a :- Either a (f a) Source #

Read a => Lifting * Read ((,) a) Source # 

Methods

lifting :: (a, a) :- (a, f a) Source #

Read1 m => Lifting * Read (ListT m) Source # 

Methods

lifting :: ListT m a :- ListT m (f a) Source #

Read1 f => Lifting * Read (Lift f) Source # 

Methods

lifting :: Lift f a :- Lift f (f a) Source #

Read1 m => Lifting * Read (MaybeT m) Source # 

Methods

lifting :: MaybeT m a :- MaybeT m (f a) Source #

Show a => Lifting * Show (Either a) Source # 

Methods

lifting :: Either a a :- Either a (f a) Source #

Show a => Lifting * Show ((,) a) Source # 

Methods

lifting :: (a, a) :- (a, f a) Source #

Show1 m => Lifting * Show (ListT m) Source # 

Methods

lifting :: ListT m a :- ListT m (f a) Source #

Show1 f => Lifting * Show (Lift f) Source # 

Methods

lifting :: Lift f a :- Lift f (f a) Source #

Show1 m => Lifting * Show (MaybeT m) Source # 

Methods

lifting :: MaybeT m a :- MaybeT m (f a) Source #

Ix a => Lifting * Ix ((,) a) Source # 

Methods

lifting :: (a, a) :- (a, f a) Source #

Lifting * Monoid ((->) a) Source # 

Methods

lifting :: (a -> a) :- (a -> f a) Source #

Monoid a => Lifting * Monoid ((,) a) Source # 

Methods

lifting :: (a, a) :- (a, f a) Source #

Binary a => Lifting * Binary (Either a) Source # 

Methods

lifting :: Either a a :- Either a (f a) Source #

Binary a => Lifting * Binary ((,) a) Source # 

Methods

lifting :: (a, a) :- (a, f a) Source #

NFData a => Lifting * NFData (Either a) Source # 

Methods

lifting :: Either a a :- Either a (f a) Source #

NFData a => Lifting * NFData ((,) a) Source # 

Methods

lifting :: (a, a) :- (a, f a) Source #

Hashable a => Lifting * Hashable (Either a) Source # 

Methods

lifting :: Either a a :- Either a (f a) Source #

Hashable a => Lifting * Hashable ((,) a) Source # 

Methods

lifting :: (a, a) :- (a, f a) Source #

(Eq e, Eq1 m) => Lifting * Eq (ExceptT e m) Source # 

Methods

lifting :: ExceptT e m a :- ExceptT e m (f a) Source #

(Eq e, Eq1 m) => Lifting * Eq (ErrorT e m) Source # 

Methods

lifting :: ErrorT e m a :- ErrorT e m (f a) Source #

(Eq w, Eq1 m) => Lifting * Eq (WriterT w m) Source # 

Methods

lifting :: WriterT w m a :- WriterT w m (f a) Source #

(Eq w, Eq1 m) => Lifting * Eq (WriterT w m) Source # 

Methods

lifting :: WriterT w m a :- WriterT w m (f a) Source #

Eq1 f => Lifting * Eq (Reverse * f) Source # 

Methods

lifting :: Reverse * f a :- Reverse * f (f a) Source #

Eq1 f => Lifting * Eq (Backwards * f) Source # 

Methods

lifting :: Backwards * f a :- Backwards * f (f a) Source #

Eq1 m => Lifting * Eq (IdentityT * m) Source # 

Methods

lifting :: IdentityT * m a :- IdentityT * m (f a) Source #

(Ord e, Ord1 m) => Lifting * Ord (ExceptT e m) Source # 

Methods

lifting :: ExceptT e m a :- ExceptT e m (f a) Source #

(Ord e, Ord1 m) => Lifting * Ord (ErrorT e m) Source # 

Methods

lifting :: ErrorT e m a :- ErrorT e m (f a) Source #

(Ord w, Ord1 m) => Lifting * Ord (WriterT w m) Source # 

Methods

lifting :: WriterT w m a :- WriterT w m (f a) Source #

(Ord w, Ord1 m) => Lifting * Ord (WriterT w m) Source # 

Methods

lifting :: WriterT w m a :- WriterT w m (f a) Source #

Ord1 f => Lifting * Ord (Reverse * f) Source # 

Methods

lifting :: Reverse * f a :- Reverse * f (f a) Source #

Ord1 f => Lifting * Ord (Backwards * f) Source # 

Methods

lifting :: Backwards * f a :- Backwards * f (f a) Source #

Ord1 m => Lifting * Ord (IdentityT * m) Source # 

Methods

lifting :: IdentityT * m a :- IdentityT * m (f a) Source #

(Read e, Read1 m) => Lifting * Read (ExceptT e m) Source # 

Methods

lifting :: ExceptT e m a :- ExceptT e m (f a) Source #

(Read e, Read1 m) => Lifting * Read (ErrorT e m) Source # 

Methods

lifting :: ErrorT e m a :- ErrorT e m (f a) Source #

(Read w, Read1 m) => Lifting * Read (WriterT w m) Source # 

Methods

lifting :: WriterT w m a :- WriterT w m (f a) Source #

(Read w, Read1 m) => Lifting * Read (WriterT w m) Source # 

Methods

lifting :: WriterT w m a :- WriterT w m (f a) Source #

Read1 f => Lifting * Read (Reverse * f) Source # 

Methods

lifting :: Reverse * f a :- Reverse * f (f a) Source #

Read1 f => Lifting * Read (Backwards * f) Source # 

Methods

lifting :: Backwards * f a :- Backwards * f (f a) Source #

Read1 m => Lifting * Read (IdentityT * m) Source # 

Methods

lifting :: IdentityT * m a :- IdentityT * m (f a) Source #

(Show e, Show1 m) => Lifting * Show (ExceptT e m) Source # 

Methods

lifting :: ExceptT e m a :- ExceptT e m (f a) Source #

(Show e, Show1 m) => Lifting * Show (ErrorT e m) Source # 

Methods

lifting :: ErrorT e m a :- ErrorT e m (f a) Source #

(Show w, Show1 m) => Lifting * Show (WriterT w m) Source # 

Methods

lifting :: WriterT w m a :- WriterT w m (f a) Source #

(Show w, Show1 m) => Lifting * Show (WriterT w m) Source # 

Methods

lifting :: WriterT w m a :- WriterT w m (f a) Source #

Show1 f => Lifting * Show (Reverse * f) Source # 

Methods

lifting :: Reverse * f a :- Reverse * f (f a) Source #

Show1 f => Lifting * Show (Backwards * f) Source # 

Methods

lifting :: Backwards * f a :- Backwards * f (f a) Source #

Show1 m => Lifting * Show (IdentityT * m) Source # 

Methods

lifting :: IdentityT * m a :- IdentityT * m (f a) Source #

(Eq1 f, Eq1 g) => Lifting * Eq (Sum * f g) Source # 

Methods

lifting :: Sum * f g a :- Sum * f g (f a) Source #

(Eq1 f, Eq1 g) => Lifting * Eq (Product * f g) Source # 

Methods

lifting :: Product * f g a :- Product * f g (f a) Source #

(Ord1 f, Ord1 g) => Lifting * Ord (Sum * f g) Source # 

Methods

lifting :: Sum * f g a :- Sum * f g (f a) Source #

(Ord1 f, Ord1 g) => Lifting * Ord (Product * f g) Source # 

Methods

lifting :: Product * f g a :- Product * f g (f a) Source #

(Read1 f, Read1 g) => Lifting * Read (Sum * f g) Source # 

Methods

lifting :: Sum * f g a :- Sum * f g (f a) Source #

(Read1 f, Read1 g) => Lifting * Read (Product * f g) Source # 

Methods

lifting :: Product * f g a :- Product * f g (f a) Source #

(Show1 f, Show1 g) => Lifting * Show (Sum * f g) Source # 

Methods

lifting :: Sum * f g a :- Sum * f g (f a) Source #

(Show1 f, Show1 g) => Lifting * Show (Product * f g) Source # 

Methods

lifting :: Product * f g a :- Product * f g (f a) Source #

(Eq1 f, Eq1 g) => Lifting * Eq (Compose * * f g) Source # 

Methods

lifting :: Compose * * f g a :- Compose * * f g (f a) Source #

(Ord1 f, Ord1 g) => Lifting * Ord (Compose * * f g) Source # 

Methods

lifting :: Compose * * f g a :- Compose * * f g (f a) Source #

(Read1 f, Read1 g) => Lifting * Read (Compose * * f g) Source # 

Methods

lifting :: Compose * * f g a :- Compose * * f g (f a) Source #

(Show1 f, Show1 g) => Lifting * Show (Compose * * f g) Source # 

Methods

lifting :: Compose * * f g a :- Compose * * f g (f a) Source #

Lifting (* -> *) Monad ListT Source # 

Methods

lifting :: ListT a :- ListT (f a) Source #

Lifting (* -> *) Monad MaybeT Source # 

Methods

lifting :: MaybeT a :- MaybeT (f a) Source #

Lifting (* -> *) Functor ListT Source # 

Methods

lifting :: ListT a :- ListT (f a) Source #

Lifting (* -> *) Functor Lift Source # 

Methods

lifting :: Lift a :- Lift (f a) Source #

Lifting (* -> *) Functor MaybeT Source # 

Methods

lifting :: MaybeT a :- MaybeT (f a) Source #

Lifting (* -> *) Applicative ListT Source # 

Methods

lifting :: ListT a :- ListT (f a) Source #

Lifting (* -> *) Applicative Lift Source # 

Methods

lifting :: Lift a :- Lift (f a) Source #

Lifting (* -> *) Foldable ListT Source # 

Methods

lifting :: ListT a :- ListT (f a) Source #

Lifting (* -> *) Foldable Lift Source # 

Methods

lifting :: Lift a :- Lift (f a) Source #

Lifting (* -> *) Foldable MaybeT Source # 

Methods

lifting :: MaybeT a :- MaybeT (f a) Source #

Lifting (* -> *) Traversable ListT Source # 

Methods

lifting :: ListT a :- ListT (f a) Source #

Lifting (* -> *) Traversable Lift Source # 

Methods

lifting :: Lift a :- Lift (f a) Source #

Lifting (* -> *) Traversable MaybeT Source # 

Methods

lifting :: MaybeT a :- MaybeT (f a) Source #

Lifting (* -> *) Eq1 ListT Source # 

Methods

lifting :: ListT a :- ListT (f a) Source #

Lifting (* -> *) Eq1 Lift Source # 

Methods

lifting :: Lift a :- Lift (f a) Source #

Lifting (* -> *) Eq1 MaybeT Source # 

Methods

lifting :: MaybeT a :- MaybeT (f a) Source #

Lifting (* -> *) Ord1 ListT Source # 

Methods

lifting :: ListT a :- ListT (f a) Source #

Lifting (* -> *) Ord1 Lift Source # 

Methods

lifting :: Lift a :- Lift (f a) Source #

Lifting (* -> *) Ord1 MaybeT Source # 

Methods

lifting :: MaybeT a :- MaybeT (f a) Source #

Lifting (* -> *) Read1 ListT Source # 

Methods

lifting :: ListT a :- ListT (f a) Source #

Lifting (* -> *) Read1 Lift Source # 

Methods

lifting :: Lift a :- Lift (f a) Source #

Lifting (* -> *) Read1 MaybeT Source # 

Methods

lifting :: MaybeT a :- MaybeT (f a) Source #

Lifting (* -> *) Show1 ListT Source # 

Methods

lifting :: ListT a :- ListT (f a) Source #

Lifting (* -> *) Show1 Lift Source # 

Methods

lifting :: Lift a :- Lift (f a) Source #

Lifting (* -> *) Show1 MaybeT Source # 

Methods

lifting :: MaybeT a :- MaybeT (f a) Source #

Lifting (* -> *) MonadIO ListT Source # 

Methods

lifting :: ListT a :- ListT (f a) Source #

Lifting (* -> *) MonadIO MaybeT Source # 

Methods

lifting :: MaybeT a :- MaybeT (f a) Source #

Lifting (* -> *) Alternative ListT Source # 

Methods

lifting :: ListT a :- ListT (f a) Source #

Lifting (* -> *) Alternative Lift Source # 

Methods

lifting :: Lift a :- Lift (f a) Source #

Lifting (* -> *) MonadPlus ListT Source # 

Methods

lifting :: ListT a :- ListT (f a) Source #

Lifting (* -> *) MonadPlus MaybeT Source # 

Methods

lifting :: MaybeT a :- MaybeT (f a) Source #

Lifting (* -> *) MonadCont ListT Source # 

Methods

lifting :: ListT a :- ListT (f a) Source #

Lifting (* -> *) MonadCont MaybeT Source # 

Methods

lifting :: MaybeT a :- MaybeT (f a) Source #

Lifting (* -> *) Monad (ExceptT e) Source # 

Methods

lifting :: ExceptT e a :- ExceptT e (f a) Source #

Error e => Lifting (* -> *) Monad (ErrorT e) Source # 

Methods

lifting :: ErrorT e a :- ErrorT e (f a) Source #

Lifting (* -> *) Monad (StateT s) Source # 

Methods

lifting :: StateT s a :- StateT s (f a) Source #

Lifting (* -> *) Monad (StateT s) Source # 

Methods

lifting :: StateT s a :- StateT s (f a) Source #

Monoid w => Lifting (* -> *) Monad (WriterT w) Source # 

Methods

lifting :: WriterT w a :- WriterT w (f a) Source #

Monoid w => Lifting (* -> *) Monad (WriterT w) Source # 

Methods

lifting :: WriterT w a :- WriterT w (f a) Source #

Lifting (* -> *) Monad (IdentityT *) Source # 

Methods

lifting :: IdentityT * a :- IdentityT * (f a) Source #

Lifting (* -> *) Functor (ExceptT e) Source # 

Methods

lifting :: ExceptT e a :- ExceptT e (f a) Source #

Lifting (* -> *) Functor (ErrorT e) Source # 

Methods

lifting :: ErrorT e a :- ErrorT e (f a) Source #

Lifting (* -> *) Functor (StateT s) Source # 

Methods

lifting :: StateT s a :- StateT s (f a) Source #

Lifting (* -> *) Functor (StateT s) Source # 

Methods

lifting :: StateT s a :- StateT s (f a) Source #

Lifting (* -> *) Functor (WriterT w) Source # 

Methods

lifting :: WriterT w a :- WriterT w (f a) Source #

Lifting (* -> *) Functor (WriterT w) Source # 

Methods

lifting :: WriterT w a :- WriterT w (f a) Source #

Lifting (* -> *) Functor (Reverse *) Source # 

Methods

lifting :: Reverse * a :- Reverse * (f a) Source #

Lifting (* -> *) Functor (Backwards *) Source # 

Methods

lifting :: Backwards * a :- Backwards * (f a) Source #

Lifting (* -> *) Functor (IdentityT *) Source # 

Methods

lifting :: IdentityT * a :- IdentityT * (f a) Source #

Lifting (* -> *) MonadFix (ExceptT e) Source # 

Methods

lifting :: ExceptT e a :- ExceptT e (f a) Source #

Error e => Lifting (* -> *) MonadFix (ErrorT e) Source # 

Methods

lifting :: ErrorT e a :- ErrorT e (f a) Source #

Lifting (* -> *) MonadFix (StateT s) Source # 

Methods

lifting :: StateT s a :- StateT s (f a) Source #

Lifting (* -> *) MonadFix (StateT s) Source # 

Methods

lifting :: StateT s a :- StateT s (f a) Source #

Monoid w => Lifting (* -> *) MonadFix (WriterT w) Source # 

Methods

lifting :: WriterT w a :- WriterT w (f a) Source #

Monoid w => Lifting (* -> *) MonadFix (WriterT w) Source # 

Methods

lifting :: WriterT w a :- WriterT w (f a) Source #

Lifting (* -> *) MonadFix (IdentityT *) Source # 

Methods

lifting :: IdentityT * a :- IdentityT * (f a) Source #

Monoid w => Lifting (* -> *) Applicative (WriterT w) Source # 

Methods

lifting :: WriterT w a :- WriterT w (f a) Source #

Monoid w => Lifting (* -> *) Applicative (WriterT w) Source # 

Methods

lifting :: WriterT w a :- WriterT w (f a) Source #

Lifting (* -> *) Applicative (Reverse *) Source # 

Methods

lifting :: Reverse * a :- Reverse * (f a) Source #

Lifting (* -> *) Applicative (Backwards *) Source # 

Methods

lifting :: Backwards * a :- Backwards * (f a) Source #

Lifting (* -> *) Applicative (IdentityT *) Source # 

Methods

lifting :: IdentityT * a :- IdentityT * (f a) Source #

Lifting (* -> *) Foldable (ExceptT e) Source # 

Methods

lifting :: ExceptT e a :- ExceptT e (f a) Source #

Lifting (* -> *) Foldable (ErrorT e) Source # 

Methods

lifting :: ErrorT e a :- ErrorT e (f a) Source #

Lifting (* -> *) Foldable (WriterT w) Source # 

Methods

lifting :: WriterT w a :- WriterT w (f a) Source #

Lifting (* -> *) Foldable (WriterT w) Source # 

Methods

lifting :: WriterT w a :- WriterT w (f a) Source #

Lifting (* -> *) Foldable (Reverse *) Source # 

Methods

lifting :: Reverse * a :- Reverse * (f a) Source #

Lifting (* -> *) Foldable (Backwards *) Source # 

Methods

lifting :: Backwards * a :- Backwards * (f a) Source #

Lifting (* -> *) Foldable (IdentityT *) Source # 

Methods

lifting :: IdentityT * a :- IdentityT * (f a) Source #

Lifting (* -> *) Traversable (ExceptT e) Source # 

Methods

lifting :: ExceptT e a :- ExceptT e (f a) Source #

Lifting (* -> *) Traversable (ErrorT e) Source # 

Methods

lifting :: ErrorT e a :- ErrorT e (f a) Source #

Lifting (* -> *) Traversable (WriterT w) Source # 

Methods

lifting :: WriterT w a :- WriterT w (f a) Source #

Lifting (* -> *) Traversable (WriterT w) Source # 

Methods

lifting :: WriterT w a :- WriterT w (f a) Source #

Lifting (* -> *) Traversable (Reverse *) Source # 

Methods

lifting :: Reverse * a :- Reverse * (f a) Source #

Lifting (* -> *) Traversable (Backwards *) Source # 

Methods

lifting :: Backwards * a :- Backwards * (f a) Source #

Lifting (* -> *) Traversable (IdentityT *) Source # 

Methods

lifting :: IdentityT * a :- IdentityT * (f a) Source #

Eq e => Lifting (* -> *) Eq1 (ExceptT e) Source # 

Methods

lifting :: ExceptT e a :- ExceptT e (f a) Source #

Eq e => Lifting (* -> *) Eq1 (ErrorT e) Source # 

Methods

lifting :: ErrorT e a :- ErrorT e (f a) Source #

Eq w => Lifting (* -> *) Eq1 (WriterT w) Source # 

Methods

lifting :: WriterT w a :- WriterT w (f a) Source #

Eq w => Lifting (* -> *) Eq1 (WriterT w) Source # 

Methods

lifting :: WriterT w a :- WriterT w (f a) Source #

Lifting (* -> *) Eq1 (Reverse *) Source # 

Methods

lifting :: Reverse * a :- Reverse * (f a) Source #

Lifting (* -> *) Eq1 (Backwards *) Source # 

Methods

lifting :: Backwards * a :- Backwards * (f a) Source #

Lifting (* -> *) Eq1 (IdentityT *) Source # 

Methods

lifting :: IdentityT * a :- IdentityT * (f a) Source #

Ord e => Lifting (* -> *) Ord1 (ExceptT e) Source # 

Methods

lifting :: ExceptT e a :- ExceptT e (f a) Source #

Ord e => Lifting (* -> *) Ord1 (ErrorT e) Source # 

Methods

lifting :: ErrorT e a :- ErrorT e (f a) Source #

Ord w => Lifting (* -> *) Ord1 (WriterT w) Source # 

Methods

lifting :: WriterT w a :- WriterT w (f a) Source #

Ord w => Lifting (* -> *) Ord1 (WriterT w) Source # 

Methods

lifting :: WriterT w a :- WriterT w (f a) Source #

Lifting (* -> *) Ord1 (Reverse *) Source # 

Methods

lifting :: Reverse * a :- Reverse * (f a) Source #

Lifting (* -> *) Ord1 (Backwards *) Source # 

Methods

lifting :: Backwards * a :- Backwards * (f a) Source #

Lifting (* -> *) Ord1 (IdentityT *) Source # 

Methods

lifting :: IdentityT * a :- IdentityT * (f a) Source #

Read e => Lifting (* -> *) Read1 (ExceptT e) Source # 

Methods

lifting :: ExceptT e a :- ExceptT e (f a) Source #

Read e => Lifting (* -> *) Read1 (ErrorT e) Source # 

Methods

lifting :: ErrorT e a :- ErrorT e (f a) Source #

Read w => Lifting (* -> *) Read1 (WriterT w) Source # 

Methods

lifting :: WriterT w a :- WriterT w (f a) Source #

Read w => Lifting (* -> *) Read1 (WriterT w) Source # 

Methods

lifting :: WriterT w a :- WriterT w (f a) Source #

Lifting (* -> *) Read1 (Reverse *) Source # 

Methods

lifting :: Reverse * a :- Reverse * (f a) Source #

Lifting (* -> *) Read1 (Backwards *) Source # 

Methods

lifting :: Backwards * a :- Backwards * (f a) Source #

Lifting (* -> *) Read1 (IdentityT *) Source # 

Methods

lifting :: IdentityT * a :- IdentityT * (f a) Source #

Show e => Lifting (* -> *) Show1 (ExceptT e) Source # 

Methods

lifting :: ExceptT e a :- ExceptT e (f a) Source #

Show e => Lifting (* -> *) Show1 (ErrorT e) Source # 

Methods

lifting :: ErrorT e a :- ErrorT e (f a) Source #

Show w => Lifting (* -> *) Show1 (WriterT w) Source # 

Methods

lifting :: WriterT w a :- WriterT w (f a) Source #

Show w => Lifting (* -> *) Show1 (WriterT w) Source # 

Methods

lifting :: WriterT w a :- WriterT w (f a) Source #

Lifting (* -> *) Show1 (Reverse *) Source # 

Methods

lifting :: Reverse * a :- Reverse * (f a) Source #

Lifting (* -> *) Show1 (Backwards *) Source # 

Methods

lifting :: Backwards * a :- Backwards * (f a) Source #

Lifting (* -> *) Show1 (IdentityT *) Source # 

Methods

lifting :: IdentityT * a :- IdentityT * (f a) Source #

Lifting (* -> *) MonadIO (ExceptT e) Source # 

Methods

lifting :: ExceptT e a :- ExceptT e (f a) Source #

Error e => Lifting (* -> *) MonadIO (ErrorT e) Source # 

Methods

lifting :: ErrorT e a :- ErrorT e (f a) Source #

Lifting (* -> *) MonadIO (StateT s) Source # 

Methods

lifting :: StateT s a :- StateT s (f a) Source #

Lifting (* -> *) MonadIO (StateT s) Source # 

Methods

lifting :: StateT s a :- StateT s (f a) Source #

Monoid w => Lifting (* -> *) MonadIO (WriterT w) Source # 

Methods

lifting :: WriterT w a :- WriterT w (f a) Source #

Monoid w => Lifting (* -> *) MonadIO (WriterT w) Source # 

Methods

lifting :: WriterT w a :- WriterT w (f a) Source #

Lifting (* -> *) MonadIO (IdentityT *) Source # 

Methods

lifting :: IdentityT * a :- IdentityT * (f a) Source #

Monoid w => Lifting (* -> *) Alternative (WriterT w) Source # 

Methods

lifting :: WriterT w a :- WriterT w (f a) Source #

Monoid w => Lifting (* -> *) Alternative (WriterT w) Source # 

Methods

lifting :: WriterT w a :- WriterT w (f a) Source #

Lifting (* -> *) Alternative (Reverse *) Source # 

Methods

lifting :: Reverse * a :- Reverse * (f a) Source #

Lifting (* -> *) Alternative (Backwards *) Source # 

Methods

lifting :: Backwards * a :- Backwards * (f a) Source #

Lifting (* -> *) Alternative (IdentityT *) Source # 

Methods

lifting :: IdentityT * a :- IdentityT * (f a) Source #

Monoid e => Lifting (* -> *) MonadPlus (ExceptT e) Source # 

Methods

lifting :: ExceptT e a :- ExceptT e (f a) Source #

Error e => Lifting (* -> *) MonadPlus (ErrorT e) Source # 

Methods

lifting :: ErrorT e a :- ErrorT e (f a) Source #

Lifting (* -> *) MonadPlus (StateT s) Source # 

Methods

lifting :: StateT s a :- StateT s (f a) Source #

Lifting (* -> *) MonadPlus (StateT s) Source # 

Methods

lifting :: StateT s a :- StateT s (f a) Source #

Monoid w => Lifting (* -> *) MonadPlus (WriterT w) Source # 

Methods

lifting :: WriterT w a :- WriterT w (f a) Source #

Monoid w => Lifting (* -> *) MonadPlus (WriterT w) Source # 

Methods

lifting :: WriterT w a :- WriterT w (f a) Source #

Lifting (* -> *) MonadPlus (IdentityT *) Source # 

Methods

lifting :: IdentityT * a :- IdentityT * (f a) Source #

Lifting (* -> *) MonadCont (ExceptT w) Source # 

Methods

lifting :: ExceptT w a :- ExceptT w (f a) Source #

Error e => Lifting (* -> *) MonadCont (ErrorT e) Source # 

Methods

lifting :: ErrorT e a :- ErrorT e (f a) Source #

Lifting (* -> *) MonadCont (StateT s) Source # 

Methods

lifting :: StateT s a :- StateT s (f a) Source #

Lifting (* -> *) MonadCont (StateT s) Source # 

Methods

lifting :: StateT s a :- StateT s (f a) Source #

Monoid w => Lifting (* -> *) MonadCont (WriterT w) Source # 

Methods

lifting :: WriterT w a :- WriterT w (f a) Source #

Monoid w => Lifting (* -> *) MonadCont (WriterT w) Source # 

Methods

lifting :: WriterT w a :- WriterT w (f a) Source #

Lifting (* -> *) MonadCont (IdentityT *) Source # 

Methods

lifting :: IdentityT * a :- IdentityT * (f a) Source #

Monad f => Lifting (* -> *) Monad (Product * f) Source # 

Methods

lifting :: Product * f a :- Product * f (f a) Source #

Lifting (* -> *) Monad (ContT * r) Source # 

Methods

lifting :: ContT * r a :- ContT * r (f a) Source #

Lifting (* -> *) Monad (ReaderT * e) Source # 

Methods

lifting :: ReaderT * e a :- ReaderT * e (f a) Source #

Functor f => Lifting (* -> *) Functor (Sum * f) Source # 

Methods

lifting :: Sum * f a :- Sum * f (f a) Source #

Functor f => Lifting (* -> *) Functor (Product * f) Source # 

Methods

lifting :: Product * f a :- Product * f (f a) Source #

Lifting (* -> *) Functor (ContT * r) Source # 

Methods

lifting :: ContT * r a :- ContT * r (f a) Source #

Lifting (* -> *) Functor (ReaderT * e) Source # 

Methods

lifting :: ReaderT * e a :- ReaderT * e (f a) Source #

MonadFix f => Lifting (* -> *) MonadFix (Product * f) Source # 

Methods

lifting :: Product * f a :- Product * f (f a) Source #

Lifting (* -> *) MonadFix (ReaderT * e) Source # 

Methods

lifting :: ReaderT * e a :- ReaderT * e (f a) Source #

Applicative f => Lifting (* -> *) Applicative (Product * f) Source # 

Methods

lifting :: Product * f a :- Product * f (f a) Source #

Lifting (* -> *) Applicative (ContT * r) Source # 

Methods

lifting :: ContT * r a :- ContT * r (f a) Source #

Lifting (* -> *) Applicative (ReaderT * e) Source # 

Methods

lifting :: ReaderT * e a :- ReaderT * e (f a) Source #

Foldable f => Lifting (* -> *) Foldable (Sum * f) Source # 

Methods

lifting :: Sum * f a :- Sum * f (f a) Source #

Foldable f => Lifting (* -> *) Foldable (Product * f) Source # 

Methods

lifting :: Product * f a :- Product * f (f a) Source #

Traversable f => Lifting (* -> *) Traversable (Sum * f) Source # 

Methods

lifting :: Sum * f a :- Sum * f (f a) Source #

Traversable f => Lifting (* -> *) Traversable (Product * f) Source # 

Methods

lifting :: Product * f a :- Product * f (f a) Source #

Eq1 f => Lifting (* -> *) Eq1 (Sum * f) Source # 

Methods

lifting :: Sum * f a :- Sum * f (f a) Source #

Eq1 f => Lifting (* -> *) Eq1 (Product * f) Source # 

Methods

lifting :: Product * f a :- Product * f (f a) Source #

Ord1 f => Lifting (* -> *) Ord1 (Sum * f) Source # 

Methods

lifting :: Sum * f a :- Sum * f (f a) Source #

Ord1 f => Lifting (* -> *) Ord1 (Product * f) Source # 

Methods

lifting :: Product * f a :- Product * f (f a) Source #

Read1 f => Lifting (* -> *) Read1 (Sum * f) Source # 

Methods

lifting :: Sum * f a :- Sum * f (f a) Source #

Read1 f => Lifting (* -> *) Read1 (Product * f) Source # 

Methods

lifting :: Product * f a :- Product * f (f a) Source #

Show1 f => Lifting (* -> *) Show1 (Sum * f) Source # 

Methods

lifting :: Sum * f a :- Sum * f (f a) Source #

Show1 f => Lifting (* -> *) Show1 (Product * f) Source # 

Methods

lifting :: Product * f a :- Product * f (f a) Source #

Lifting (* -> *) MonadIO (ContT * r) Source # 

Methods

lifting :: ContT * r a :- ContT * r (f a) Source #

Lifting (* -> *) MonadIO (ReaderT * e) Source # 

Methods

lifting :: ReaderT * e a :- ReaderT * e (f a) Source #

Alternative f => Lifting (* -> *) Alternative (Product * f) Source # 

Methods

lifting :: Product * f a :- Product * f (f a) Source #

Lifting (* -> *) Alternative (ReaderT * e) Source # 

Methods

lifting :: ReaderT * e a :- ReaderT * e (f a) Source #

MonadPlus f => Lifting (* -> *) MonadPlus (Product * f) Source # 

Methods

lifting :: Product * f a :- Product * f (f a) Source #

Lifting (* -> *) MonadPlus (ReaderT * e) Source # 

Methods

lifting :: ReaderT * e a :- ReaderT * e (f a) Source #

Lifting (* -> *) MonadCont (ReaderT * e) Source # 

Methods

lifting :: ReaderT * e a :- ReaderT * e (f a) Source #

Monoid w => Lifting (* -> *) Monad (RWST r w s) Source # 

Methods

lifting :: RWST r w s a :- RWST r w s (f a) Source #

Monoid w => Lifting (* -> *) Monad (RWST r w s) Source # 

Methods

lifting :: RWST r w s a :- RWST r w s (f a) Source #

Functor f => Lifting (* -> *) Functor (Compose * * f) Source # 

Methods

lifting :: Compose * * f a :- Compose * * f (f a) Source #

Lifting (* -> *) Functor (RWST r w s) Source # 

Methods

lifting :: RWST r w s a :- RWST r w s (f a) Source #

Lifting (* -> *) Functor (RWST r w s) Source # 

Methods

lifting :: RWST r w s a :- RWST r w s (f a) Source #

Monoid w => Lifting (* -> *) MonadFix (RWST r w s) Source # 

Methods

lifting :: RWST r w s a :- RWST r w s (f a) Source #

Monoid w => Lifting (* -> *) MonadFix (RWST r w s) Source # 

Methods

lifting :: RWST r w s a :- RWST r w s (f a) Source #

Applicative f => Lifting (* -> *) Applicative (Compose * * f) Source # 

Methods

lifting :: Compose * * f a :- Compose * * f (f a) Source #

Foldable f => Lifting (* -> *) Foldable (Compose * * f) Source # 

Methods

lifting :: Compose * * f a :- Compose * * f (f a) Source #

Traversable f => Lifting (* -> *) Traversable (Compose * * f) Source # 

Methods

lifting :: Compose * * f a :- Compose * * f (f a) Source #

Eq1 f => Lifting (* -> *) Eq1 (Compose * * f) Source # 

Methods

lifting :: Compose * * f a :- Compose * * f (f a) Source #

Ord1 f => Lifting (* -> *) Ord1 (Compose * * f) Source # 

Methods

lifting :: Compose * * f a :- Compose * * f (f a) Source #

Read1 f => Lifting (* -> *) Read1 (Compose * * f) Source # 

Methods

lifting :: Compose * * f a :- Compose * * f (f a) Source #

Show1 f => Lifting (* -> *) Show1 (Compose * * f) Source # 

Methods

lifting :: Compose * * f a :- Compose * * f (f a) Source #

Monoid w => Lifting (* -> *) MonadIO (RWST r w s) Source # 

Methods

lifting :: RWST r w s a :- RWST r w s (f a) Source #

Monoid w => Lifting (* -> *) MonadIO (RWST r w s) Source # 

Methods

lifting :: RWST r w s a :- RWST r w s (f a) Source #

Alternative f => Lifting (* -> *) Alternative (Compose * * f) Source # 

Methods

lifting :: Compose * * f a :- Compose * * f (f a) Source #

Monoid w => Lifting (* -> *) MonadPlus (RWST r w s) Source # 

Methods

lifting :: RWST r w s a :- RWST r w s (f a) Source #

Monoid w => Lifting (* -> *) MonadPlus (RWST r w s) Source # 

Methods

lifting :: RWST r w s a :- RWST r w s (f a) Source #

Monoid w => Lifting (* -> *) MonadCont (RWST r w s) Source # 

Methods

lifting :: RWST r w s a :- RWST r w s (f a) Source #

Monoid w => Lifting (* -> *) MonadCont (RWST r w s) Source # 

Methods

lifting :: RWST r w s a :- RWST r w s (f a) Source #

Lifting (* -> *) (MonadError e) ListT Source # 

Methods

lifting :: ListT a :- ListT (f a) Source #

Lifting (* -> *) (MonadError e) MaybeT Source # 

Methods

lifting :: MaybeT a :- MaybeT (f a) Source #

Lifting (* -> *) (MonadReader r) ListT Source # 

Methods

lifting :: ListT a :- ListT (f a) Source #

Lifting (* -> *) (MonadReader r) MaybeT Source # 

Methods

lifting :: MaybeT a :- MaybeT (f a) Source #

Lifting (* -> *) (MonadState s) ListT Source # 

Methods

lifting :: ListT a :- ListT (f a) Source #

Lifting (* -> *) (MonadState s) MaybeT Source # 

Methods

lifting :: MaybeT a :- MaybeT (f a) Source #

Lifting (* -> *) (MonadError e) (StateT s) Source # 

Methods

lifting :: StateT s a :- StateT s (f a) Source #

Lifting (* -> *) (MonadError e) (StateT s) Source # 

Methods

lifting :: StateT s a :- StateT s (f a) Source #

Monoid w => Lifting (* -> *) (MonadError e) (WriterT w) Source # 

Methods

lifting :: WriterT w a :- WriterT w (f a) Source #

Monoid w => Lifting (* -> *) (MonadError e) (WriterT w) Source # 

Methods

lifting :: WriterT w a :- WriterT w (f a) Source #

Lifting (* -> *) (MonadError e) (IdentityT *) Source # 

Methods

lifting :: IdentityT * a :- IdentityT * (f a) Source #

Error e => Lifting (* -> *) (MonadReader r) (ErrorT e) Source # 

Methods

lifting :: ErrorT e a :- ErrorT e (f a) Source #

Lifting (* -> *) (MonadReader r) (ExceptT e) Source # 

Methods

lifting :: ExceptT e a :- ExceptT e (f a) Source #

Lifting (* -> *) (MonadReader r) (StateT s) Source # 

Methods

lifting :: StateT s a :- StateT s (f a) Source #

Lifting (* -> *) (MonadReader r) (StateT s) Source # 

Methods

lifting :: StateT s a :- StateT s (f a) Source #

Monoid w => Lifting (* -> *) (MonadReader r) (WriterT w) Source # 

Methods

lifting :: WriterT w a :- WriterT w (f a) Source #

Monoid w => Lifting (* -> *) (MonadReader r) (WriterT w) Source # 

Methods

lifting :: WriterT w a :- WriterT w (f a) Source #

Lifting (* -> *) (MonadReader r) (IdentityT *) Source # 

Methods

lifting :: IdentityT * a :- IdentityT * (f a) Source #

Error e => Lifting (* -> *) (MonadState s) (ErrorT e) Source # 

Methods

lifting :: ErrorT e a :- ErrorT e (f a) Source #

Lifting (* -> *) (MonadState s) (ExceptT e) Source # 

Methods

lifting :: ExceptT e a :- ExceptT e (f a) Source #

Monoid w => Lifting (* -> *) (MonadState s) (WriterT w) Source # 

Methods

lifting :: WriterT w a :- WriterT w (f a) Source #

Monoid w => Lifting (* -> *) (MonadState s) (WriterT w) Source # 

Methods

lifting :: WriterT w a :- WriterT w (f a) Source #

Lifting (* -> *) (MonadState s) (IdentityT *) Source # 

Methods

lifting :: IdentityT * a :- IdentityT * (f a) Source #

Lifting (* -> *) (MonadError e) (ReaderT * r) Source # 

Methods

lifting :: ReaderT * r a :- ReaderT * r (f a) Source #

Lifting (* -> *) (MonadReader r) (ContT * r') Source # 

Methods

lifting :: ContT * r' a :- ContT * r' (f a) Source #

Lifting (* -> *) (MonadState s) (ContT * r') Source # 

Methods

lifting :: ContT * r' a :- ContT * r' (f a) Source #

Lifting (* -> *) (MonadState s) (ReaderT * r) Source # 

Methods

lifting :: ReaderT * r a :- ReaderT * r (f a) Source #

Monoid w => Lifting (* -> *) (MonadError e) (RWST r w s) Source # 

Methods

lifting :: RWST r w s a :- RWST r w s (f a) Source #

Monoid w => Lifting (* -> *) (MonadError e) (RWST r w s) Source # 

Methods

lifting :: RWST r w s a :- RWST r w s (f a) Source #

Lifting (* -> *) (MonadRWS r w s) MaybeT Source # 

Methods

lifting :: MaybeT a :- MaybeT (f a) Source #

Lifting (* -> *) (MonadRWS r w s) (ExceptT e) Source # 

Methods

lifting :: ExceptT e a :- ExceptT e (f a) Source #

Error e => Lifting (* -> *) (MonadRWS r w s) (ErrorT e) Source # 

Methods

lifting :: ErrorT e a :- ErrorT e (f a) Source #

Lifting (* -> *) (MonadRWS r w s) (IdentityT *) Source # 

Methods

lifting :: IdentityT * a :- IdentityT * (f a) Source #

class Lifting2 p f where Source #

Minimal complete definition

lifting2

Methods

lifting2 :: p a :- Lifting p (f a) Source #

Instances

Lifting2 * Bounded (,) Source # 

Methods

lifting2 :: (,) a :- Lifting Bounded (,) (f a) Source #

Lifting2 * Eq Either Source # 
Lifting2 * Eq (,) Source # 

Methods

lifting2 :: (,) a :- Lifting Eq (,) (f a) Source #

Lifting2 * Ord Either Source # 
Lifting2 * Ord (,) Source # 

Methods

lifting2 :: (,) a :- Lifting Ord (,) (f a) Source #

Lifting2 * Read Either Source # 
Lifting2 * Read (,) Source # 

Methods

lifting2 :: (,) a :- Lifting Read (,) (f a) Source #

Lifting2 * Show Either Source # 
Lifting2 * Show (,) Source # 

Methods

lifting2 :: (,) a :- Lifting Show (,) (f a) Source #

Lifting2 * Ix (,) Source # 

Methods

lifting2 :: (,) a :- Lifting Ix (,) (f a) Source #

Lifting2 * Monoid (,) Source # 

Methods

lifting2 :: (,) a :- Lifting Monoid (,) (f a) Source #

Lifting2 * Binary Either Source # 
Lifting2 * Binary (,) Source # 

Methods

lifting2 :: (,) a :- Lifting Binary (,) (f a) Source #

Lifting2 * NFData Either Source # 
Lifting2 * NFData (,) Source # 

Methods

lifting2 :: (,) a :- Lifting NFData (,) (f a) Source #

Lifting2 * Hashable Either Source # 
Lifting2 * Hashable (,) Source # 
Lifting2 (* -> *) Monad (Product *) Source # 
Lifting2 (* -> *) Functor (Sum *) Source # 

Methods

lifting2 :: Sum * a :- Lifting Functor (Sum *) (f a) Source #

Lifting2 (* -> *) Functor (Product *) Source # 
Lifting2 (* -> *) MonadFix (Product *) Source # 
Lifting2 (* -> *) Applicative (Product *) Source # 
Lifting2 (* -> *) Foldable (Sum *) Source # 

Methods

lifting2 :: Sum * a :- Lifting Foldable (Sum *) (f a) Source #

Lifting2 (* -> *) Foldable (Product *) Source # 
Lifting2 (* -> *) Traversable (Sum *) Source # 

Methods

lifting2 :: Sum * a :- Lifting Traversable (Sum *) (f a) Source #

Lifting2 (* -> *) Traversable (Product *) Source # 
Lifting2 (* -> *) Eq1 (Sum *) Source # 

Methods

lifting2 :: Sum * a :- Lifting Eq1 (Sum *) (f a) Source #

Lifting2 (* -> *) Eq1 (Product *) Source # 

Methods

lifting2 :: Product * a :- Lifting Eq1 (Product *) (f a) Source #

Lifting2 (* -> *) Ord1 (Sum *) Source # 

Methods

lifting2 :: Sum * a :- Lifting Ord1 (Sum *) (f a) Source #

Lifting2 (* -> *) Ord1 (Product *) Source # 
Lifting2 (* -> *) Read1 (Sum *) Source # 

Methods

lifting2 :: Sum * a :- Lifting Read1 (Sum *) (f a) Source #

Lifting2 (* -> *) Read1 (Product *) Source # 
Lifting2 (* -> *) Show1 (Sum *) Source # 

Methods

lifting2 :: Sum * a :- Lifting Show1 (Sum *) (f a) Source #

Lifting2 (* -> *) Show1 (Product *) Source # 
Lifting2 (* -> *) Alternative (Product *) Source # 
Lifting2 (* -> *) MonadPlus (Product *) Source # 
Lifting2 (* -> *) Functor (Compose * *) Source # 
Lifting2 (* -> *) Applicative (Compose * *) Source # 
Lifting2 (* -> *) Foldable (Compose * *) Source # 
Lifting2 (* -> *) Traversable (Compose * *) Source # 
Lifting2 (* -> *) Alternative (Compose * *) Source #