constraints-0.13.4: Constraint manipulation
Safe HaskellNone
LanguageHaskell2010

Data.Constraint.Lifting

Documentation

class Lifting p f where Source #

Methods

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

Instances

Instances details
Lifting Eq [] Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Eq a :- Eq [a] Source #

Lifting Eq Maybe Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Eq a :- Eq (Maybe a) Source #

Lifting Eq Ratio Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Eq a :- Eq (Ratio a) Source #

Lifting Eq Complex Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Eq a :- Eq (Complex a) Source #

Lifting Eq Identity Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Eq a :- Eq (Identity a) Source #

Lifting Ord [] Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Ord a :- Ord [a] Source #

Lifting Ord Maybe Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Ord a :- Ord (Maybe a) Source #

Lifting Ord Identity Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Ord a :- Ord (Identity a) Source #

Lifting Read [] Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Read a :- Read [a] Source #

Lifting Read Maybe Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Read a :- Read (Maybe a) Source #

Lifting Read Complex Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Read a :- Read (Complex a) Source #

Lifting Read Identity Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Read a :- Read (Identity a) Source #

Lifting Show [] Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Show a :- Show [a] Source #

Lifting Show Maybe Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Show a :- Show (Maybe a) Source #

Lifting Show Complex Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Show a :- Show (Complex a) Source #

Lifting Show Identity Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Show a :- Show (Identity a) Source #

Lifting Semigroup Maybe Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Semigroup a :- Semigroup (Maybe a) Source #

Lifting Monoid Maybe Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Monoid a :- Monoid (Maybe a) Source #

Lifting Binary [] Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Binary a :- Binary [a] Source #

Lifting Binary Maybe Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Binary a :- Binary (Maybe a) Source #

Lifting NFData [] Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). NFData a :- NFData [a] Source #

Lifting NFData Maybe Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). NFData a :- NFData (Maybe a) Source #

Lifting Hashable [] Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Hashable a :- Hashable [a] Source #

Lifting Hashable Maybe Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Hashable a :- Hashable (Maybe a) Source #

Bounded a => Lifting Bounded ((,) a :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a0 :: k). Bounded a0 :- Bounded (a, a0) Source #

Eq a => Lifting Eq (Either a :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a0 :: k). Eq a0 :- Eq (Either a a0) Source #

Eq a => Lifting Eq ((,) a :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a0 :: k). Eq a0 :- Eq (a, a0) Source #

Eq1 m => Lifting Eq (ListT m :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Eq a :- Eq (ListT m a) Source #

Eq1 f => Lifting Eq (Lift f :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Eq a :- Eq (Lift f a) Source #

Eq1 m => Lifting Eq (MaybeT m :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Eq a :- Eq (MaybeT m a) Source #

Ord a => Lifting Ord (Either a :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a0 :: k). Ord a0 :- Ord (Either a a0) Source #

Ord a => Lifting Ord ((,) a :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a0 :: k). Ord a0 :- Ord (a, a0) Source #

Ord1 m => Lifting Ord (ListT m :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Ord a :- Ord (ListT m a) Source #

Ord1 f => Lifting Ord (Lift f :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Ord a :- Ord (Lift f a) Source #

Ord1 m => Lifting Ord (MaybeT m :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Ord a :- Ord (MaybeT m a) Source #

Read a => Lifting Read (Either a :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a0 :: k). Read a0 :- Read (Either a a0) Source #

Read a => Lifting Read ((,) a :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a0 :: k). Read a0 :- Read (a, a0) Source #

Read1 m => Lifting Read (ListT m :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Read a :- Read (ListT m a) Source #

Read1 f => Lifting Read (Lift f :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Read a :- Read (Lift f a) Source #

Read1 m => Lifting Read (MaybeT m :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Read a :- Read (MaybeT m a) Source #

Show a => Lifting Show (Either a :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a0 :: k). Show a0 :- Show (Either a a0) Source #

Show a => Lifting Show ((,) a :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a0 :: k). Show a0 :- Show (a, a0) Source #

Show1 m => Lifting Show (ListT m :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Show a :- Show (ListT m a) Source #

Show1 f => Lifting Show (Lift f :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Show a :- Show (Lift f a) Source #

Show1 m => Lifting Show (MaybeT m :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Show a :- Show (MaybeT m a) Source #

Ix a => Lifting Ix ((,) a :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a0 :: k). Ix a0 :- Ix (a, a0) Source #

Semigroup a => Lifting Semigroup ((,) a :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a0 :: k). Semigroup a0 :- Semigroup (a, a0) Source #

Monoid a => Lifting Monoid ((,) a :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a0 :: k). Monoid a0 :- Monoid (a, a0) Source #

Binary a => Lifting Binary (Either a :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a0 :: k). Binary a0 :- Binary (Either a a0) Source #

Binary a => Lifting Binary ((,) a :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a0 :: k). Binary a0 :- Binary (a, a0) Source #

NFData a => Lifting NFData (Either a :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a0 :: k). NFData a0 :- NFData (Either a a0) Source #

NFData a => Lifting NFData ((,) a :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a0 :: k). NFData a0 :- NFData (a, a0) Source #

Hashable a => Lifting Hashable (Either a :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a0 :: k). Hashable a0 :- Hashable (Either a a0) Source #

Hashable a => Lifting Hashable ((,) a :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a0 :: k). Hashable a0 :- Hashable (a, a0) Source #

Eq1 m => Lifting Eq (IdentityT m :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Eq a :- Eq (IdentityT m a) Source #

(Eq e, Eq1 m) => Lifting Eq (ErrorT e m :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Eq a :- Eq (ErrorT e m a) Source #

(Eq e, Eq1 m) => Lifting Eq (ExceptT e m :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Eq a :- Eq (ExceptT e m a) Source #

(Eq w, Eq1 m) => Lifting Eq (WriterT w m :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Eq a :- Eq (WriterT w m a) Source #

(Eq w, Eq1 m) => Lifting Eq (WriterT w m :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Eq a :- Eq (WriterT w m a) Source #

Eq1 f => Lifting Eq (Reverse f :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Eq a :- Eq (Reverse f a) Source #

Eq1 f => Lifting Eq (Backwards f :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Eq a :- Eq (Backwards f a) Source #

Ord1 m => Lifting Ord (IdentityT m :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Ord a :- Ord (IdentityT m a) Source #

(Ord e, Ord1 m) => Lifting Ord (ErrorT e m :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Ord a :- Ord (ErrorT e m a) Source #

(Ord e, Ord1 m) => Lifting Ord (ExceptT e m :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Ord a :- Ord (ExceptT e m a) Source #

(Ord w, Ord1 m) => Lifting Ord (WriterT w m :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Ord a :- Ord (WriterT w m a) Source #

(Ord w, Ord1 m) => Lifting Ord (WriterT w m :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Ord a :- Ord (WriterT w m a) Source #

Ord1 f => Lifting Ord (Reverse f :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Ord a :- Ord (Reverse f a) Source #

Ord1 f => Lifting Ord (Backwards f :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Ord a :- Ord (Backwards f a) Source #

Read1 m => Lifting Read (IdentityT m :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Read a :- Read (IdentityT m a) Source #

(Read e, Read1 m) => Lifting Read (ErrorT e m :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Read a :- Read (ErrorT e m a) Source #

(Read e, Read1 m) => Lifting Read (ExceptT e m :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Read a :- Read (ExceptT e m a) Source #

(Read w, Read1 m) => Lifting Read (WriterT w m :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Read a :- Read (WriterT w m a) Source #

(Read w, Read1 m) => Lifting Read (WriterT w m :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Read a :- Read (WriterT w m a) Source #

Read1 f => Lifting Read (Reverse f :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Read a :- Read (Reverse f a) Source #

Read1 f => Lifting Read (Backwards f :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Read a :- Read (Backwards f a) Source #

Show1 m => Lifting Show (IdentityT m :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Show a :- Show (IdentityT m a) Source #

(Show e, Show1 m) => Lifting Show (ErrorT e m :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Show a :- Show (ErrorT e m a) Source #

(Show e, Show1 m) => Lifting Show (ExceptT e m :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Show a :- Show (ExceptT e m a) Source #

(Show w, Show1 m) => Lifting Show (WriterT w m :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Show a :- Show (WriterT w m a) Source #

(Show w, Show1 m) => Lifting Show (WriterT w m :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Show a :- Show (WriterT w m a) Source #

Show1 f => Lifting Show (Reverse f :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Show a :- Show (Reverse f a) Source #

Show1 f => Lifting Show (Backwards f :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Show a :- Show (Backwards f a) Source #

(Eq1 f, Eq1 g) => Lifting Eq (Product f g :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Eq a :- Eq (Product f g a) Source #

(Eq1 f, Eq1 g) => Lifting Eq (Sum f g :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Eq a :- Eq (Sum f g a) Source #

(Ord1 f, Ord1 g) => Lifting Ord (Product f g :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Ord a :- Ord (Product f g a) Source #

(Ord1 f, Ord1 g) => Lifting Ord (Sum f g :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Ord a :- Ord (Sum f g a) Source #

(Read1 f, Read1 g) => Lifting Read (Product f g :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Read a :- Read (Product f g a) Source #

(Read1 f, Read1 g) => Lifting Read (Sum f g :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Read a :- Read (Sum f g a) Source #

(Show1 f, Show1 g) => Lifting Show (Product f g :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Show a :- Show (Product f g a) Source #

(Show1 f, Show1 g) => Lifting Show (Sum f g :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Show a :- Show (Sum f g a) Source #

Lifting Semigroup ((->) a :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a0 :: k). Semigroup a0 :- Semigroup (a -> a0) Source #

Lifting Monoid ((->) a :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a0 :: k). Monoid a0 :- Monoid (a -> a0) Source #

(Eq1 f, Eq1 g) => Lifting Eq (Compose f g :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Eq a :- Eq (Compose f g a) Source #

(Ord1 f, Ord1 g) => Lifting Ord (Compose f g :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Ord a :- Ord (Compose f g a) Source #

(Read1 f, Read1 g) => Lifting Read (Compose f g :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Read a :- Read (Compose f g a) Source #

(Show1 f, Show1 g) => Lifting Show (Compose f g :: Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Show a :- Show (Compose f g a) Source #

Lifting Monad ListT Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Monad a :- Monad (ListT a) Source #

Lifting Monad MaybeT Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Monad a :- Monad (MaybeT a) Source #

Lifting Functor ListT Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Functor a :- Functor (ListT a) Source #

Lifting Functor Lift Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Functor a :- Functor (Lift a) Source #

Lifting Functor MaybeT Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Functor a :- Functor (MaybeT a) Source #

Lifting Applicative ListT Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Applicative a :- Applicative (ListT a) Source #

Lifting Applicative Lift Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Applicative a :- Applicative (Lift a) Source #

Lifting Foldable ListT Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Foldable a :- Foldable (ListT a) Source #

Lifting Foldable Lift Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Foldable a :- Foldable (Lift a) Source #

Lifting Foldable MaybeT Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Foldable a :- Foldable (MaybeT a) Source #

Lifting Traversable ListT Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Traversable a :- Traversable (ListT a) Source #

Lifting Traversable Lift Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Traversable a :- Traversable (Lift a) Source #

Lifting Traversable MaybeT Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Traversable a :- Traversable (MaybeT a) Source #

Lifting Eq1 ListT Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Eq1 a :- Eq1 (ListT a) Source #

Lifting Eq1 Lift Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Eq1 a :- Eq1 (Lift a) Source #

Lifting Eq1 MaybeT Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Eq1 a :- Eq1 (MaybeT a) Source #

Lifting Ord1 ListT Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Ord1 a :- Ord1 (ListT a) Source #

Lifting Ord1 Lift Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Ord1 a :- Ord1 (Lift a) Source #

Lifting Ord1 MaybeT Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Ord1 a :- Ord1 (MaybeT a) Source #

Lifting Read1 ListT Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Read1 a :- Read1 (ListT a) Source #

Lifting Read1 Lift Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Read1 a :- Read1 (Lift a) Source #

Lifting Read1 MaybeT Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Read1 a :- Read1 (MaybeT a) Source #

Lifting Show1 ListT Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Show1 a :- Show1 (ListT a) Source #

Lifting Show1 Lift Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Show1 a :- Show1 (Lift a) Source #

Lifting Show1 MaybeT Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Show1 a :- Show1 (MaybeT a) Source #

Lifting MonadIO ListT Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadIO a :- MonadIO (ListT a) Source #

Lifting MonadIO MaybeT Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadIO a :- MonadIO (MaybeT a) Source #

Lifting Alternative ListT Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Alternative a :- Alternative (ListT a) Source #

Lifting Alternative Lift Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Alternative a :- Alternative (Lift a) Source #

Lifting MonadPlus ListT Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadPlus a :- MonadPlus (ListT a) Source #

Lifting MonadPlus MaybeT Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadPlus a :- MonadPlus (MaybeT a) Source #

Lifting MonadCont ListT Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadCont a :- MonadCont (ListT a) Source #

Lifting MonadCont MaybeT Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadCont a :- MonadCont (MaybeT a) Source #

Lifting Monad (IdentityT :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Monad a :- Monad (IdentityT a) Source #

Error e => Lifting Monad (ErrorT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Monad a :- Monad (ErrorT e a) Source #

Lifting Monad (ExceptT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Monad a :- Monad (ExceptT e a) Source #

Lifting Monad (ReaderT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Monad a :- Monad (ReaderT e a) Source #

Lifting Monad (StateT s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Monad a :- Monad (StateT s a) Source #

Lifting Monad (StateT s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Monad a :- Monad (StateT s a) Source #

Monoid w => Lifting Monad (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Monad a :- Monad (WriterT w a) Source #

Monoid w => Lifting Monad (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Monad a :- Monad (WriterT w a) Source #

Lifting Functor (IdentityT :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Functor a :- Functor (IdentityT a) Source #

Lifting Functor (ErrorT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Functor a :- Functor (ErrorT e a) Source #

Lifting Functor (ExceptT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Functor a :- Functor (ExceptT e a) Source #

Lifting Functor (ReaderT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Functor a :- Functor (ReaderT e a) Source #

Lifting Functor (StateT s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Functor a :- Functor (StateT s a) Source #

Lifting Functor (StateT s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Functor a :- Functor (StateT s a) Source #

Lifting Functor (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Functor a :- Functor (WriterT w a) Source #

Lifting Functor (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Functor a :- Functor (WriterT w a) Source #

Lifting Functor (Reverse :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Functor a :- Functor (Reverse a) Source #

Lifting Functor (Backwards :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Functor a :- Functor (Backwards a) Source #

Lifting MonadFix (IdentityT :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadFix a :- MonadFix (IdentityT a) Source #

Error e => Lifting MonadFix (ErrorT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadFix a :- MonadFix (ErrorT e a) Source #

Lifting MonadFix (ExceptT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadFix a :- MonadFix (ExceptT e a) Source #

Lifting MonadFix (ReaderT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadFix a :- MonadFix (ReaderT e a) Source #

Lifting MonadFix (StateT s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadFix a :- MonadFix (StateT s a) Source #

Lifting MonadFix (StateT s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadFix a :- MonadFix (StateT s a) Source #

Monoid w => Lifting MonadFix (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadFix a :- MonadFix (WriterT w a) Source #

Monoid w => Lifting MonadFix (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadFix a :- MonadFix (WriterT w a) Source #

Lifting Applicative (IdentityT :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Applicative a :- Applicative (IdentityT a) Source #

Lifting Applicative (ReaderT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Applicative a :- Applicative (ReaderT e a) Source #

Monoid w => Lifting Applicative (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Applicative a :- Applicative (WriterT w a) Source #

Monoid w => Lifting Applicative (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Applicative a :- Applicative (WriterT w a) Source #

Lifting Applicative (Reverse :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Applicative a :- Applicative (Reverse a) Source #

Lifting Applicative (Backwards :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Applicative a :- Applicative (Backwards a) Source #

Lifting Foldable (IdentityT :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Foldable a :- Foldable (IdentityT a) Source #

Lifting Foldable (ErrorT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Foldable a :- Foldable (ErrorT e a) Source #

Lifting Foldable (ExceptT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Foldable a :- Foldable (ExceptT e a) Source #

Lifting Foldable (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Foldable a :- Foldable (WriterT w a) Source #

Lifting Foldable (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Foldable a :- Foldable (WriterT w a) Source #

Lifting Foldable (Reverse :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Foldable a :- Foldable (Reverse a) Source #

Lifting Foldable (Backwards :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Foldable a :- Foldable (Backwards a) Source #

Lifting Traversable (IdentityT :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Traversable a :- Traversable (IdentityT a) Source #

Lifting Traversable (ErrorT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Traversable a :- Traversable (ErrorT e a) Source #

Lifting Traversable (ExceptT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Traversable a :- Traversable (ExceptT e a) Source #

Lifting Traversable (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Traversable a :- Traversable (WriterT w a) Source #

Lifting Traversable (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Traversable a :- Traversable (WriterT w a) Source #

Lifting Traversable (Reverse :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Traversable a :- Traversable (Reverse a) Source #

Lifting Traversable (Backwards :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Traversable a :- Traversable (Backwards a) Source #

Lifting Eq1 (IdentityT :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Eq1 a :- Eq1 (IdentityT a) Source #

Eq e => Lifting Eq1 (ErrorT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Eq1 a :- Eq1 (ErrorT e a) Source #

Eq e => Lifting Eq1 (ExceptT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Eq1 a :- Eq1 (ExceptT e a) Source #

Eq w => Lifting Eq1 (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Eq1 a :- Eq1 (WriterT w a) Source #

Eq w => Lifting Eq1 (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Eq1 a :- Eq1 (WriterT w a) Source #

Lifting Eq1 (Reverse :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Eq1 a :- Eq1 (Reverse a) Source #

Lifting Eq1 (Backwards :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Eq1 a :- Eq1 (Backwards a) Source #

Lifting Ord1 (IdentityT :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Ord1 a :- Ord1 (IdentityT a) Source #

Ord e => Lifting Ord1 (ErrorT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Ord1 a :- Ord1 (ErrorT e a) Source #

Ord e => Lifting Ord1 (ExceptT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Ord1 a :- Ord1 (ExceptT e a) Source #

Ord w => Lifting Ord1 (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Ord1 a :- Ord1 (WriterT w a) Source #

Ord w => Lifting Ord1 (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Ord1 a :- Ord1 (WriterT w a) Source #

Lifting Ord1 (Reverse :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Ord1 a :- Ord1 (Reverse a) Source #

Lifting Ord1 (Backwards :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Ord1 a :- Ord1 (Backwards a) Source #

Lifting Read1 (IdentityT :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Read1 a :- Read1 (IdentityT a) Source #

Read e => Lifting Read1 (ErrorT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Read1 a :- Read1 (ErrorT e a) Source #

Read e => Lifting Read1 (ExceptT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Read1 a :- Read1 (ExceptT e a) Source #

Read w => Lifting Read1 (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Read1 a :- Read1 (WriterT w a) Source #

Read w => Lifting Read1 (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Read1 a :- Read1 (WriterT w a) Source #

Lifting Read1 (Reverse :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Read1 a :- Read1 (Reverse a) Source #

Lifting Read1 (Backwards :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Read1 a :- Read1 (Backwards a) Source #

Lifting Show1 (IdentityT :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Show1 a :- Show1 (IdentityT a) Source #

Show e => Lifting Show1 (ErrorT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Show1 a :- Show1 (ErrorT e a) Source #

Show e => Lifting Show1 (ExceptT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Show1 a :- Show1 (ExceptT e a) Source #

Show w => Lifting Show1 (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Show1 a :- Show1 (WriterT w a) Source #

Show w => Lifting Show1 (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Show1 a :- Show1 (WriterT w a) Source #

Lifting Show1 (Reverse :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Show1 a :- Show1 (Reverse a) Source #

Lifting Show1 (Backwards :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Show1 a :- Show1 (Backwards a) Source #

Lifting MonadIO (IdentityT :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadIO a :- MonadIO (IdentityT a) Source #

Error e => Lifting MonadIO (ErrorT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadIO a :- MonadIO (ErrorT e a) Source #

Lifting MonadIO (ExceptT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadIO a :- MonadIO (ExceptT e a) Source #

Lifting MonadIO (ReaderT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadIO a :- MonadIO (ReaderT e a) Source #

Lifting MonadIO (StateT s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadIO a :- MonadIO (StateT s a) Source #

Lifting MonadIO (StateT s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadIO a :- MonadIO (StateT s a) Source #

Monoid w => Lifting MonadIO (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadIO a :- MonadIO (WriterT w a) Source #

Monoid w => Lifting MonadIO (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadIO a :- MonadIO (WriterT w a) Source #

Lifting Alternative (IdentityT :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Alternative a :- Alternative (IdentityT a) Source #

Lifting Alternative (ReaderT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Alternative a :- Alternative (ReaderT e a) Source #

Monoid w => Lifting Alternative (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Alternative a :- Alternative (WriterT w a) Source #

Monoid w => Lifting Alternative (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Alternative a :- Alternative (WriterT w a) Source #

Lifting Alternative (Reverse :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Alternative a :- Alternative (Reverse a) Source #

Lifting Alternative (Backwards :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Alternative a :- Alternative (Backwards a) Source #

Lifting MonadPlus (IdentityT :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadPlus a :- MonadPlus (IdentityT a) Source #

Error e => Lifting MonadPlus (ErrorT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadPlus a :- MonadPlus (ErrorT e a) Source #

Monoid e => Lifting MonadPlus (ExceptT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadPlus a :- MonadPlus (ExceptT e a) Source #

Lifting MonadPlus (ReaderT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadPlus a :- MonadPlus (ReaderT e a) Source #

Lifting MonadPlus (StateT s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadPlus a :- MonadPlus (StateT s a) Source #

Lifting MonadPlus (StateT s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadPlus a :- MonadPlus (StateT s a) Source #

Monoid w => Lifting MonadPlus (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadPlus a :- MonadPlus (WriterT w a) Source #

Monoid w => Lifting MonadPlus (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadPlus a :- MonadPlus (WriterT w a) Source #

Lifting MonadCont (IdentityT :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadCont a :- MonadCont (IdentityT a) Source #

Error e => Lifting MonadCont (ErrorT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadCont a :- MonadCont (ErrorT e a) Source #

Lifting MonadCont (ExceptT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadCont a :- MonadCont (ExceptT w a) Source #

Lifting MonadCont (ReaderT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadCont a :- MonadCont (ReaderT e a) Source #

Lifting MonadCont (StateT s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadCont a :- MonadCont (StateT s a) Source #

Lifting MonadCont (StateT s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadCont a :- MonadCont (StateT s a) Source #

Monoid w => Lifting MonadCont (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadCont a :- MonadCont (WriterT w a) Source #

Monoid w => Lifting MonadCont (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadCont a :- MonadCont (WriterT w a) Source #

Monad f => Lifting Monad (Product f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Monad a :- Monad (Product f a) Source #

Lifting Monad (ContT r :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Monad a :- Monad (ContT r a) Source #

Functor f => Lifting Functor (Product f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Functor a :- Functor (Product f a) Source #

Functor f => Lifting Functor (Sum f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Functor a :- Functor (Sum f a) Source #

Lifting Functor (ContT r :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Functor a :- Functor (ContT r a) Source #

MonadFix f => Lifting MonadFix (Product f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadFix a :- MonadFix (Product f a) Source #

Applicative f => Lifting Applicative (Product f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Applicative a :- Applicative (Product f a) Source #

Lifting Applicative (ContT r :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Applicative a :- Applicative (ContT r a) Source #

Foldable f => Lifting Foldable (Product f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Foldable a :- Foldable (Product f a) Source #

Foldable f => Lifting Foldable (Sum f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Foldable a :- Foldable (Sum f a) Source #

Traversable f => Lifting Traversable (Product f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Traversable a :- Traversable (Product f a) Source #

Traversable f => Lifting Traversable (Sum f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Traversable a :- Traversable (Sum f a) Source #

Eq1 f => Lifting Eq1 (Product f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Eq1 a :- Eq1 (Product f a) Source #

Eq1 f => Lifting Eq1 (Sum f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Eq1 a :- Eq1 (Sum f a) Source #

Ord1 f => Lifting Ord1 (Product f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Ord1 a :- Ord1 (Product f a) Source #

Ord1 f => Lifting Ord1 (Sum f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Ord1 a :- Ord1 (Sum f a) Source #

Read1 f => Lifting Read1 (Product f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Read1 a :- Read1 (Product f a) Source #

Read1 f => Lifting Read1 (Sum f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Read1 a :- Read1 (Sum f a) Source #

Show1 f => Lifting Show1 (Product f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Show1 a :- Show1 (Product f a) Source #

Show1 f => Lifting Show1 (Sum f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Show1 a :- Show1 (Sum f a) Source #

Lifting MonadIO (ContT r :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadIO a :- MonadIO (ContT r a) Source #

Alternative f => Lifting Alternative (Product f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Alternative a :- Alternative (Product f a) Source #

MonadPlus f => Lifting MonadPlus (Product f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadPlus a :- MonadPlus (Product f a) Source #

Monoid w => Lifting Monad (RWST r w s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Monad a :- Monad (RWST r w s a) Source #

Monoid w => Lifting Monad (RWST r w s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Monad a :- Monad (RWST r w s a) Source #

Functor f => Lifting Functor (Compose f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Functor a :- Functor (Compose f a) Source #

Lifting Functor (RWST r w s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Functor a :- Functor (RWST r w s a) Source #

Lifting Functor (RWST r w s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Functor a :- Functor (RWST r w s a) Source #

Monoid w => Lifting MonadFix (RWST r w s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadFix a :- MonadFix (RWST r w s a) Source #

Monoid w => Lifting MonadFix (RWST r w s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadFix a :- MonadFix (RWST r w s a) Source #

Applicative f => Lifting Applicative (Compose f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Applicative a :- Applicative (Compose f a) Source #

Foldable f => Lifting Foldable (Compose f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Foldable a :- Foldable (Compose f a) Source #

Traversable f => Lifting Traversable (Compose f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Traversable a :- Traversable (Compose f a) Source #

Eq1 f => Lifting Eq1 (Compose f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Eq1 a :- Eq1 (Compose f a) Source #

Ord1 f => Lifting Ord1 (Compose f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Ord1 a :- Ord1 (Compose f a) Source #

Read1 f => Lifting Read1 (Compose f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Read1 a :- Read1 (Compose f a) Source #

Show1 f => Lifting Show1 (Compose f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Show1 a :- Show1 (Compose f a) Source #

Monoid w => Lifting MonadIO (RWST r w s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadIO a :- MonadIO (RWST r w s a) Source #

Monoid w => Lifting MonadIO (RWST r w s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadIO a :- MonadIO (RWST r w s a) Source #

Alternative f => Lifting Alternative (Compose f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). Alternative a :- Alternative (Compose f a) Source #

Monoid w => Lifting MonadPlus (RWST r w s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadPlus a :- MonadPlus (RWST r w s a) Source #

Monoid w => Lifting MonadPlus (RWST r w s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadPlus a :- MonadPlus (RWST r w s a) Source #

Monoid w => Lifting MonadCont (RWST r w s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadCont a :- MonadCont (RWST r w s a) Source #

Monoid w => Lifting MonadCont (RWST r w s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadCont a :- MonadCont (RWST r w s a) Source #

Lifting (MonadState s :: (Type -> Type) -> Constraint) ListT Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadState s a :- MonadState s (ListT a) Source #

Lifting (MonadState s :: (Type -> Type) -> Constraint) MaybeT Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadState s a :- MonadState s (MaybeT a) Source #

Lifting (MonadReader r :: (Type -> Type) -> Constraint) ListT Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadReader r a :- MonadReader r (ListT a) Source #

Lifting (MonadReader r :: (Type -> Type) -> Constraint) MaybeT Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadReader r a :- MonadReader r (MaybeT a) Source #

Lifting (MonadError e :: (Type -> Type) -> Constraint) ListT Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadError e a :- MonadError e (ListT a) Source #

Lifting (MonadError e :: (Type -> Type) -> Constraint) MaybeT Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadError e a :- MonadError e (MaybeT a) Source #

Error e => Lifting (MonadState s :: (Type -> Type) -> Constraint) (ErrorT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadState s a :- MonadState s (ErrorT e a) Source #

Lifting (MonadState s :: (Type -> Type) -> Constraint) (ExceptT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadState s a :- MonadState s (ExceptT e a) Source #

Lifting (MonadState s :: (Type -> Type) -> Constraint) (ReaderT r :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadState s a :- MonadState s (ReaderT r a) Source #

Monoid w => Lifting (MonadState s :: (Type -> Type) -> Constraint) (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadState s a :- MonadState s (WriterT w a) Source #

Monoid w => Lifting (MonadState s :: (Type -> Type) -> Constraint) (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadState s a :- MonadState s (WriterT w a) Source #

Lifting (MonadState s :: (Type -> Type) -> Constraint) (IdentityT :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadState s a :- MonadState s (IdentityT a) Source #

Error e => Lifting (MonadReader r :: (Type -> Type) -> Constraint) (ErrorT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadReader r a :- MonadReader r (ErrorT e a) Source #

Lifting (MonadReader r :: (Type -> Type) -> Constraint) (ExceptT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadReader r a :- MonadReader r (ExceptT e a) Source #

Lifting (MonadReader r :: (Type -> Type) -> Constraint) (StateT s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadReader r a :- MonadReader r (StateT s a) Source #

Lifting (MonadReader r :: (Type -> Type) -> Constraint) (StateT s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadReader r a :- MonadReader r (StateT s a) Source #

Monoid w => Lifting (MonadReader r :: (Type -> Type) -> Constraint) (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadReader r a :- MonadReader r (WriterT w a) Source #

Monoid w => Lifting (MonadReader r :: (Type -> Type) -> Constraint) (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadReader r a :- MonadReader r (WriterT w a) Source #

Lifting (MonadReader r :: (Type -> Type) -> Constraint) (IdentityT :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadReader r a :- MonadReader r (IdentityT a) Source #

Lifting (MonadError e :: (Type -> Type) -> Constraint) (ReaderT r :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadError e a :- MonadError e (ReaderT r a) Source #

Lifting (MonadError e :: (Type -> Type) -> Constraint) (StateT s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadError e a :- MonadError e (StateT s a) Source #

Lifting (MonadError e :: (Type -> Type) -> Constraint) (StateT s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadError e a :- MonadError e (StateT s a) Source #

Monoid w => Lifting (MonadError e :: (Type -> Type) -> Constraint) (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadError e a :- MonadError e (WriterT w a) Source #

Monoid w => Lifting (MonadError e :: (Type -> Type) -> Constraint) (WriterT w :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadError e a :- MonadError e (WriterT w a) Source #

Lifting (MonadError e :: (Type -> Type) -> Constraint) (IdentityT :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadError e a :- MonadError e (IdentityT a) Source #

Lifting (MonadState s :: (Type -> Type) -> Constraint) (ContT r' :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadState s a :- MonadState s (ContT r' a) Source #

Lifting (MonadReader r :: (Type -> Type) -> Constraint) (ContT r' :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadReader r a :- MonadReader r (ContT r' a) Source #

Monoid w => Lifting (MonadError e :: (Type -> Type) -> Constraint) (RWST r w s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadError e a :- MonadError e (RWST r w s a) Source #

Monoid w => Lifting (MonadError e :: (Type -> Type) -> Constraint) (RWST r w s :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadError e a :- MonadError e (RWST r w s a) Source #

Lifting (MonadRWS r w s :: (Type -> Type) -> Constraint) MaybeT Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadRWS r w s a :- MonadRWS r w s (MaybeT a) Source #

Error e => Lifting (MonadRWS r w s :: (Type -> Type) -> Constraint) (ErrorT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadRWS r w s a :- MonadRWS r w s (ErrorT e a) Source #

Lifting (MonadRWS r w s :: (Type -> Type) -> Constraint) (ExceptT e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadRWS r w s a :- MonadRWS r w s (ExceptT e a) Source #

Lifting (MonadRWS r w s :: (Type -> Type) -> Constraint) (IdentityT :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting :: forall (a :: k). MonadRWS r w s a :- MonadRWS r w s (IdentityT a) Source #

class Lifting2 p f where Source #

Methods

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

Instances

Instances details
Lifting2 Bounded (,) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). Bounded a :- Lifting Bounded ((,) a) Source #

Lifting2 Eq Either Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). Eq a :- Lifting Eq (Either a) Source #

Lifting2 Eq (,) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). Eq a :- Lifting Eq ((,) a) Source #

Lifting2 Ord Either Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). Ord a :- Lifting Ord (Either a) Source #

Lifting2 Ord (,) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). Ord a :- Lifting Ord ((,) a) Source #

Lifting2 Read Either Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). Read a :- Lifting Read (Either a) Source #

Lifting2 Read (,) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). Read a :- Lifting Read ((,) a) Source #

Lifting2 Show Either Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). Show a :- Lifting Show (Either a) Source #

Lifting2 Show (,) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). Show a :- Lifting Show ((,) a) Source #

Lifting2 Ix (,) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). Ix a :- Lifting Ix ((,) a) Source #

Lifting2 Semigroup (,) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). Semigroup a :- Lifting Semigroup ((,) a) Source #

Lifting2 Monoid (,) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). Monoid a :- Lifting Monoid ((,) a) Source #

Lifting2 Binary Either Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). Binary a :- Lifting Binary (Either a) Source #

Lifting2 Binary (,) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). Binary a :- Lifting Binary ((,) a) Source #

Lifting2 NFData Either Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). NFData a :- Lifting NFData (Either a) Source #

Lifting2 NFData (,) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). NFData a :- Lifting NFData ((,) a) Source #

Lifting2 Hashable Either Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). Hashable a :- Lifting Hashable (Either a) Source #

Lifting2 Hashable (,) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). Hashable a :- Lifting Hashable ((,) a) Source #

Lifting2 Monad (Product :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). Monad a :- Lifting Monad (Product a) Source #

Lifting2 Functor (Product :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). Functor a :- Lifting Functor (Product a) Source #

Lifting2 Functor (Sum :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). Functor a :- Lifting Functor (Sum a) Source #

Lifting2 MonadFix (Product :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). MonadFix a :- Lifting MonadFix (Product a) Source #

Lifting2 Applicative (Product :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). Applicative a :- Lifting Applicative (Product a) Source #

Lifting2 Foldable (Product :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). Foldable a :- Lifting Foldable (Product a) Source #

Lifting2 Foldable (Sum :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). Foldable a :- Lifting Foldable (Sum a) Source #

Lifting2 Traversable (Product :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). Traversable a :- Lifting Traversable (Product a) Source #

Lifting2 Traversable (Sum :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). Traversable a :- Lifting Traversable (Sum a) Source #

Lifting2 Eq1 (Product :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). Eq1 a :- Lifting Eq1 (Product a) Source #

Lifting2 Eq1 (Sum :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). Eq1 a :- Lifting Eq1 (Sum a) Source #

Lifting2 Ord1 (Product :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). Ord1 a :- Lifting Ord1 (Product a) Source #

Lifting2 Ord1 (Sum :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). Ord1 a :- Lifting Ord1 (Sum a) Source #

Lifting2 Read1 (Product :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). Read1 a :- Lifting Read1 (Product a) Source #

Lifting2 Read1 (Sum :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). Read1 a :- Lifting Read1 (Sum a) Source #

Lifting2 Show1 (Product :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). Show1 a :- Lifting Show1 (Product a) Source #

Lifting2 Show1 (Sum :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). Show1 a :- Lifting Show1 (Sum a) Source #

Lifting2 Alternative (Product :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). Alternative a :- Lifting Alternative (Product a) Source #

Lifting2 MonadPlus (Product :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). MonadPlus a :- Lifting MonadPlus (Product a) Source #

Lifting2 Functor (Compose :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). Functor a :- Lifting Functor (Compose a) Source #

Lifting2 Applicative (Compose :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). Applicative a :- Lifting Applicative (Compose a) Source #

Lifting2 Foldable (Compose :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). Foldable a :- Lifting Foldable (Compose a) Source #

Lifting2 Traversable (Compose :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). Traversable a :- Lifting Traversable (Compose a) Source #

Lifting2 Alternative (Compose :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.Constraint.Lifting

Methods

lifting2 :: forall (a :: k). Alternative a :- Lifting Alternative (Compose a) Source #