constraints-0.6: Constraint manipulation

Safe HaskellNone
LanguageHaskell2010

Data.Constraint.Lifting

Documentation

class Lifting p f where Source

Methods

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

Instances

Lifting * Eq [] Source 
Lifting * Eq Ratio Source 
Lifting * Eq Identity Source 
Lifting * Eq Complex Source 
Lifting * Eq Maybe Source 
Lifting * Ord [] Source 
Lifting * Ord Identity Source 
Lifting * Ord Maybe Source 
Lifting * Read [] Source 
Lifting * Read Identity Source 
Lifting * Read Complex Source 
Lifting * Read Maybe Source 
Lifting * Show [] Source 
Lifting * Show Identity Source 
Lifting * Show Complex Source 
Lifting * Show Maybe Source 
Lifting * Monoid Maybe Source 
Lifting * Binary [] Source 
Lifting * Binary Maybe Source 
Lifting * NFData [] Source 
Lifting * NFData Maybe Source 
Lifting * Hashable [] Source 
Lifting * Hashable Maybe Source 
Bounded a => Lifting * Bounded ((,) a) Source 
Eq a => Lifting * Eq (Either a) Source 
Eq a => Lifting * Eq ((,) a) Source 
Eq1 m => Lifting * Eq (ListT m) Source 
Eq1 f => Lifting * Eq (Reverse f) Source 
Eq1 f => Lifting * Eq (Backwards f) Source 
Eq1 m => Lifting * Eq (MaybeT m) Source 
Eq1 m => Lifting * Eq (IdentityT m) Source 
Eq1 f => Lifting * Eq (Lift f) Source 
Ord a => Lifting * Ord (Either a) Source 
Ord a => Lifting * Ord ((,) a) Source 
Ord1 m => Lifting * Ord (ListT m) Source 
Ord1 f => Lifting * Ord (Reverse f) Source 
Ord1 f => Lifting * Ord (Backwards f) Source 
Ord1 m => Lifting * Ord (MaybeT m) Source 
Ord1 m => Lifting * Ord (IdentityT m) Source 
Ord1 f => Lifting * Ord (Lift f) Source 
Read a => Lifting * Read (Either a) Source 
Read a => Lifting * Read ((,) a) Source 
Read1 m => Lifting * Read (ListT m) Source 
Read1 f => Lifting * Read (Reverse f) Source 
Read1 f => Lifting * Read (Backwards f) Source 
Read1 m => Lifting * Read (MaybeT m) Source 
Read1 m => Lifting * Read (IdentityT m) Source 
Read1 f => Lifting * Read (Lift f) Source 
Show a => Lifting * Show (Either a) Source 
Show a => Lifting * Show ((,) a) Source 
Show1 m => Lifting * Show (ListT m) Source 
Show1 f => Lifting * Show (Reverse f) Source 
Show1 f => Lifting * Show (Backwards f) Source 
Show1 m => Lifting * Show (MaybeT m) Source 
Show1 m => Lifting * Show (IdentityT m) Source 
Show1 f => Lifting * Show (Lift f) Source 
Ix a => Lifting * Ix ((,) a) Source 
Lifting * Monoid ((->) a) Source 
Monoid a => Lifting * Monoid ((,) a) Source 
Binary a => Lifting * Binary (Either a) Source 
Binary a => Lifting * Binary ((,) a) Source 
NFData a => Lifting * NFData (Either a) Source 
NFData a => Lifting * NFData ((,) a) Source 
Hashable a => Lifting * Hashable (Either a) Source 
Hashable a => Lifting * Hashable ((,) a) Source 
(Eq e, Eq1 m) => Lifting * Eq (ExceptT e m) Source 
(Eq e, Eq1 m) => Lifting * Eq (ErrorT e m) Source 
(Eq w, Eq1 m) => Lifting * Eq (WriterT w m) Source 
(Eq w, Eq1 m) => Lifting * Eq (WriterT w m) Source 
(Eq1 f, Eq1 g) => Lifting * Eq (Sum f g) Source 
(Eq1 f, Eq1 g) => Lifting * Eq (Product f g) Source 
(Functor f, Eq1 f, Eq1 g) => Lifting * Eq (Compose f g) Source 
(Ord e, Ord1 m) => Lifting * Ord (ExceptT e m) Source 
(Ord e, Ord1 m) => Lifting * Ord (ErrorT e m) Source 
(Ord w, Ord1 m) => Lifting * Ord (WriterT w m) Source 
(Ord w, Ord1 m) => Lifting * Ord (WriterT w m) Source 
(Ord1 f, Ord1 g) => Lifting * Ord (Sum f g) Source 
(Ord1 f, Ord1 g) => Lifting * Ord (Product f g) Source 
(Functor f, Ord1 f, Ord1 g) => Lifting * Ord (Compose f g) Source 
(Read e, Read1 m) => Lifting * Read (ExceptT e m) Source 
(Read e, Read1 m) => Lifting * Read (ErrorT e m) Source 
(Read w, Read1 m) => Lifting * Read (WriterT w m) Source 
(Read w, Read1 m) => Lifting * Read (WriterT w m) Source 
(Read1 f, Read1 g) => Lifting * Read (Sum f g) Source 
(Read1 f, Read1 g) => Lifting * Read (Product f g) Source 
(Functor f, Read1 f, Read1 g) => Lifting * Read (Compose f g) Source 
(Show e, Show1 m) => Lifting * Show (ExceptT e m) Source 
(Show e, Show1 m) => Lifting * Show (ErrorT e m) Source 
(Show w, Show1 m) => Lifting * Show (WriterT w m) Source 
(Show w, Show1 m) => Lifting * Show (WriterT w m) Source 
(Show1 f, Show1 g) => Lifting * Show (Sum f g) Source 
(Show1 f, Show1 g) => Lifting * Show (Product f g) Source 
(Functor f, Show1 f, Show1 g) => Lifting * Show (Compose f g) Source 
Lifting (* -> *) Monad ListT Source 
Lifting (* -> *) Monad MaybeT Source 
Lifting (* -> *) Monad IdentityT Source 
Lifting (* -> *) Functor ListT Source 
Lifting (* -> *) Functor Reverse Source 
Lifting (* -> *) Functor Backwards Source 
Lifting (* -> *) Functor MaybeT Source 
Lifting (* -> *) Functor IdentityT Source 
Lifting (* -> *) Functor Lift Source 
Lifting (* -> *) MonadFix IdentityT Source 
Lifting (* -> *) Applicative ListT Source 
Lifting (* -> *) Applicative Reverse Source 
Lifting (* -> *) Applicative Backwards Source 
Lifting (* -> *) Applicative IdentityT Source 
Lifting (* -> *) Applicative Lift Source 
Lifting (* -> *) Foldable ListT Source 
Lifting (* -> *) Foldable Reverse Source 
Lifting (* -> *) Foldable Backwards Source 
Lifting (* -> *) Foldable MaybeT Source 
Lifting (* -> *) Foldable IdentityT Source 
Lifting (* -> *) Foldable Lift Source 
Lifting (* -> *) Traversable ListT Source 
Lifting (* -> *) Traversable Reverse Source 
Lifting (* -> *) Traversable Backwards Source 
Lifting (* -> *) Traversable MaybeT Source 
Lifting (* -> *) Traversable IdentityT Source 
Lifting (* -> *) Traversable Lift Source 
Lifting (* -> *) Alternative ListT Source 
Lifting (* -> *) Alternative Reverse Source 
Lifting (* -> *) Alternative Backwards Source 
Lifting (* -> *) Alternative IdentityT Source 
Lifting (* -> *) Alternative Lift Source 
Lifting (* -> *) MonadPlus ListT Source 
Lifting (* -> *) MonadPlus MaybeT Source 
Lifting (* -> *) MonadPlus IdentityT Source 
Lifting (* -> *) MonadIO ListT Source 
Lifting (* -> *) MonadIO MaybeT Source 
Lifting (* -> *) MonadIO IdentityT Source 
Lifting (* -> *) MonadCont ListT Source 
Lifting (* -> *) MonadCont MaybeT Source 
Lifting (* -> *) MonadCont IdentityT Source 
Lifting (* -> *) Eq1 ListT Source 
Lifting (* -> *) Eq1 Reverse Source 
Lifting (* -> *) Eq1 Backwards Source 
Lifting (* -> *) Eq1 MaybeT Source 
Lifting (* -> *) Eq1 IdentityT Source 
Lifting (* -> *) Eq1 Lift Source 
Lifting (* -> *) Ord1 ListT Source 
Lifting (* -> *) Ord1 Reverse Source 
Lifting (* -> *) Ord1 Backwards Source 
Lifting (* -> *) Ord1 MaybeT Source 
Lifting (* -> *) Ord1 IdentityT Source 
Lifting (* -> *) Ord1 Lift Source 
Lifting (* -> *) Read1 ListT Source 
Lifting (* -> *) Read1 Reverse Source 
Lifting (* -> *) Read1 Backwards Source 
Lifting (* -> *) Read1 MaybeT Source 
Lifting (* -> *) Read1 IdentityT Source 
Lifting (* -> *) Read1 Lift Source 
Lifting (* -> *) Show1 ListT Source 
Lifting (* -> *) Show1 Reverse Source 
Lifting (* -> *) Show1 Backwards Source 
Lifting (* -> *) Show1 MaybeT Source 
Lifting (* -> *) Show1 IdentityT Source 
Lifting (* -> *) Show1 Lift Source 
Lifting (* -> *) Monad (ContT r) Source 
Lifting (* -> *) Monad (ReaderT e) Source 
Lifting (* -> *) Monad (StateT s) Source 
Lifting (* -> *) Monad (StateT s) Source 
Lifting (* -> *) Monad (ExceptT e) Source 
Error e => Lifting (* -> *) Monad (ErrorT e) Source 
Monoid w => Lifting (* -> *) Monad (WriterT w) Source 
Monoid w => Lifting (* -> *) Monad (WriterT w) Source 
Monad f => Lifting (* -> *) Monad (Product f) Source 
Lifting (* -> *) Functor (ContT r) Source 
Lifting (* -> *) Functor (ReaderT e) Source 
Lifting (* -> *) Functor (StateT s) Source 
Lifting (* -> *) Functor (StateT s) Source 
Lifting (* -> *) Functor (ExceptT e) Source 
Lifting (* -> *) Functor (ErrorT e) Source 
Lifting (* -> *) Functor (WriterT w) Source 
Lifting (* -> *) Functor (WriterT w) Source 
Functor f => Lifting (* -> *) Functor (Sum f) Source 
Functor f => Lifting (* -> *) Functor (Product f) Source 
Functor f => Lifting (* -> *) Functor (Compose f) Source 
Lifting (* -> *) MonadFix (ReaderT e) Source 
Lifting (* -> *) MonadFix (StateT s) Source 
Lifting (* -> *) MonadFix (StateT s) Source 
Lifting (* -> *) MonadFix (ExceptT e) Source 
Error e => Lifting (* -> *) MonadFix (ErrorT e) Source 
Monoid w => Lifting (* -> *) MonadFix (WriterT w) Source 
Monoid w => Lifting (* -> *) MonadFix (WriterT w) Source 
MonadFix f => Lifting (* -> *) MonadFix (Product f) Source 
Lifting (* -> *) Applicative (ContT r) Source 
Lifting (* -> *) Applicative (ReaderT e) Source 
Monoid w => Lifting (* -> *) Applicative (WriterT w) Source 
Monoid w => Lifting (* -> *) Applicative (WriterT w) Source 
Applicative f => Lifting (* -> *) Applicative (Product f) Source 
Applicative f => Lifting (* -> *) Applicative (Compose f) Source 
Lifting (* -> *) Foldable (ExceptT e) Source 
Lifting (* -> *) Foldable (ErrorT e) Source 
Lifting (* -> *) Foldable (WriterT w) Source 
Lifting (* -> *) Foldable (WriterT w) Source 
Foldable f => Lifting (* -> *) Foldable (Sum f) Source 
Foldable f => Lifting (* -> *) Foldable (Product f) Source 
Foldable f => Lifting (* -> *) Foldable (Compose f) Source 
Lifting (* -> *) Traversable (ExceptT e) Source 
Lifting (* -> *) Traversable (ErrorT e) Source 
Lifting (* -> *) Traversable (WriterT w) Source 
Lifting (* -> *) Traversable (WriterT w) Source 
Traversable f => Lifting (* -> *) Traversable (Sum f) Source 
Traversable f => Lifting (* -> *) Traversable (Product f) Source 
Traversable f => Lifting (* -> *) Traversable (Compose f) Source 
Lifting (* -> *) Alternative (ReaderT e) Source 
Monoid w => Lifting (* -> *) Alternative (WriterT w) Source 
Monoid w => Lifting (* -> *) Alternative (WriterT w) Source 
Alternative f => Lifting (* -> *) Alternative (Product f) Source 
Alternative f => Lifting (* -> *) Alternative (Compose f) Source 
Lifting (* -> *) MonadPlus (ReaderT e) Source 
Lifting (* -> *) MonadPlus (StateT s) Source 
Lifting (* -> *) MonadPlus (StateT s) Source 
Monoid e => Lifting (* -> *) MonadPlus (ExceptT e) Source 
Error e => Lifting (* -> *) MonadPlus (ErrorT e) Source 
Monoid w => Lifting (* -> *) MonadPlus (WriterT w) Source 
Monoid w => Lifting (* -> *) MonadPlus (WriterT w) Source 
MonadPlus f => Lifting (* -> *) MonadPlus (Product f) Source 
Lifting (* -> *) MonadIO (ContT r) Source 
Lifting (* -> *) MonadIO (ReaderT e) Source 
Lifting (* -> *) MonadIO (StateT s) Source 
Lifting (* -> *) MonadIO (StateT s) Source 
Lifting (* -> *) MonadIO (ExceptT e) Source 
Error e => Lifting (* -> *) MonadIO (ErrorT e) Source 
Monoid w => Lifting (* -> *) MonadIO (WriterT w) Source 
Monoid w => Lifting (* -> *) MonadIO (WriterT w) Source 
Lifting (* -> *) MonadCont (ReaderT e) Source 
Lifting (* -> *) MonadCont (StateT s) Source 
Lifting (* -> *) MonadCont (StateT s) Source 
Lifting (* -> *) MonadCont (ExceptT w) Source 
Error e => Lifting (* -> *) MonadCont (ErrorT e) Source 
Monoid w => Lifting (* -> *) MonadCont (WriterT w) Source 
Monoid w => Lifting (* -> *) MonadCont (WriterT w) Source 
Eq e => Lifting (* -> *) Eq1 (ExceptT e) Source 
Eq e => Lifting (* -> *) Eq1 (ErrorT e) Source 
Eq w => Lifting (* -> *) Eq1 (WriterT w) Source 
Eq w => Lifting (* -> *) Eq1 (WriterT w) Source 
Eq1 f => Lifting (* -> *) Eq1 (Sum f) Source 
Eq1 f => Lifting (* -> *) Eq1 (Product f) Source 
(Functor f, Eq1 f) => Lifting (* -> *) Eq1 (Compose f) Source 
Ord e => Lifting (* -> *) Ord1 (ExceptT e) Source 
Ord e => Lifting (* -> *) Ord1 (ErrorT e) Source 
Ord w => Lifting (* -> *) Ord1 (WriterT w) Source 
Ord w => Lifting (* -> *) Ord1 (WriterT w) Source 
Ord1 f => Lifting (* -> *) Ord1 (Sum f) Source 
Ord1 f => Lifting (* -> *) Ord1 (Product f) Source 
(Functor f, Ord1 f) => Lifting (* -> *) Ord1 (Compose f) Source 
Read e => Lifting (* -> *) Read1 (ExceptT e) Source 
Read e => Lifting (* -> *) Read1 (ErrorT e) Source 
Read w => Lifting (* -> *) Read1 (WriterT w) Source 
Read w => Lifting (* -> *) Read1 (WriterT w) Source 
Read1 f => Lifting (* -> *) Read1 (Sum f) Source 
Read1 f => Lifting (* -> *) Read1 (Product f) Source 
(Functor f, Read1 f) => Lifting (* -> *) Read1 (Compose f) Source 
Show e => Lifting (* -> *) Show1 (ExceptT e) Source 
Show e => Lifting (* -> *) Show1 (ErrorT e) Source 
Show w => Lifting (* -> *) Show1 (WriterT w) Source 
Show w => Lifting (* -> *) Show1 (WriterT w) Source 
Show1 f => Lifting (* -> *) Show1 (Sum f) Source 
Show1 f => Lifting (* -> *) Show1 (Product f) Source 
(Functor f, Show1 f) => Lifting (* -> *) Show1 (Compose f) Source 
Monoid w => Lifting (* -> *) Monad (RWST r w s) Source 
Monoid w => Lifting (* -> *) Monad (RWST r w s) Source 
Lifting (* -> *) Functor (RWST r w s) Source 
Lifting (* -> *) Functor (RWST r w s) Source 
Monoid w => Lifting (* -> *) MonadFix (RWST r w s) Source 
Monoid w => Lifting (* -> *) MonadFix (RWST r w s) Source 
Monoid w => Lifting (* -> *) MonadPlus (RWST r w s) Source 
Monoid w => Lifting (* -> *) MonadPlus (RWST r w s) Source 
Monoid w => Lifting (* -> *) MonadIO (RWST r w s) Source 
Monoid w => Lifting (* -> *) MonadIO (RWST r w s) Source 
Monoid w => Lifting (* -> *) MonadCont (RWST r w s) Source 
Monoid w => Lifting (* -> *) MonadCont (RWST r w s) Source 
Lifting (* -> *) (MonadError e) IdentityT Source 
Lifting (* -> *) (MonadError e) ListT Source 
Lifting (* -> *) (MonadError e) MaybeT Source 
Lifting (* -> *) (MonadReader r) IdentityT Source 
Lifting (* -> *) (MonadReader r) ListT Source 
Lifting (* -> *) (MonadReader r) MaybeT Source 
Lifting (* -> *) (MonadState s) IdentityT Source 
Lifting (* -> *) (MonadState s) ListT Source 
Lifting (* -> *) (MonadState s) MaybeT Source 
Lifting (* -> *) (MonadError e) (ReaderT r) Source 
Lifting (* -> *) (MonadError e) (StateT s) Source 
Lifting (* -> *) (MonadError e) (StateT s) Source 
Monoid w => Lifting (* -> *) (MonadError e) (WriterT w) Source 
Monoid w => Lifting (* -> *) (MonadError e) (WriterT w) Source 
Lifting (* -> *) (MonadReader r) (ContT r') Source 
Error e => Lifting (* -> *) (MonadReader r) (ErrorT e) Source 
Lifting (* -> *) (MonadReader r) (ExceptT e) Source 
Lifting (* -> *) (MonadReader r) (StateT s) Source 
Lifting (* -> *) (MonadReader r) (StateT s) Source 
Monoid w => Lifting (* -> *) (MonadReader r) (WriterT w) Source 
Monoid w => Lifting (* -> *) (MonadReader r) (WriterT w) Source 
Lifting (* -> *) (MonadState s) (ContT r') Source 
Error e => Lifting (* -> *) (MonadState s) (ErrorT e) Source 
Lifting (* -> *) (MonadState s) (ExceptT e) Source 
Lifting (* -> *) (MonadState s) (ReaderT r) Source 
Monoid w => Lifting (* -> *) (MonadState s) (WriterT w) Source 
Monoid w => Lifting (* -> *) (MonadState s) (WriterT w) Source 
Monoid w => Lifting (* -> *) (MonadError e) (RWST r w s) Source 
Monoid w => Lifting (* -> *) (MonadError e) (RWST r w s) Source 
Lifting (* -> *) (MonadRWS r w s) IdentityT Source 
Lifting (* -> *) (MonadRWS r w s) MaybeT Source 
Lifting (* -> *) (MonadRWS r w s) (ExceptT e) Source 
Error e => Lifting (* -> *) (MonadRWS r w s) (ErrorT e) Source 

class Lifting2 p f where Source

Methods

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

Instances