{-# LANGUAGE CPP #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}

module Data.Constraint.Lifting
  ( Lifting(..)
  , Lifting2(..)
  ) where

import Control.Applicative
import Control.Applicative.Backwards
import Control.Applicative.Lift
import Control.DeepSeq
import Control.Monad
import Control.Monad.Cont.Class
import Control.Monad.Error.Class
import Control.Monad.Fix
import Control.Monad.IO.Class
import Control.Monad.RWS.Class
import Control.Monad.Trans.Cont
import Control.Monad.Trans.Except
import Control.Monad.Trans.Identity
import Control.Monad.Trans.Maybe
import Control.Monad.Trans.Reader
import Control.Monad.Trans.RWS.Lazy as Lazy
import Control.Monad.Trans.RWS.Strict as Strict
import Control.Monad.Trans.State.Lazy as Lazy
import Control.Monad.Trans.State.Strict as Strict
import Control.Monad.Trans.Writer.Lazy as Lazy
import Control.Monad.Trans.Writer.Strict as Strict
import Data.Binary
import Data.Complex
import Data.Constraint
import Data.Functor.Classes
import Data.Functor.Compose as Functor
import Data.Functor.Identity
import Data.Functor.Product as Functor
import Data.Functor.Reverse as Functor
import Data.Functor.Sum as Functor
import Data.Hashable
import Data.Ratio
import GHC.Arr

class Lifting p f where
  lifting :: p a :- p (f a)

instance Lifting Eq [] where lifting :: forall a. Eq a :- Eq [a]
lifting = (Eq a => Dict (Eq [a])) -> Eq a :- Eq [a]
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Eq [a])
Eq a => Dict (Eq [a])
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Ord [] where lifting :: forall a. Ord a :- Ord [a]
lifting = (Ord a => Dict (Ord [a])) -> Ord a :- Ord [a]
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Ord [a])
Ord a => Dict (Ord [a])
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Show [] where lifting :: forall a. Show a :- Show [a]
lifting = (Show a => Dict (Show [a])) -> Show a :- Show [a]
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Show [a])
Show a => Dict (Show [a])
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Read [] where lifting :: forall a. Read a :- Read [a]
lifting = (Read a => Dict (Read [a])) -> Read a :- Read [a]
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Read [a])
Read a => Dict (Read [a])
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Hashable [] where lifting :: forall a. Hashable a :- Hashable [a]
lifting = (Hashable a => Dict (Hashable [a])) -> Hashable a :- Hashable [a]
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Hashable [a])
Hashable a => Dict (Hashable [a])
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Binary [] where lifting :: forall a. Binary a :- Binary [a]
lifting = (Binary a => Dict (Binary [a])) -> Binary a :- Binary [a]
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Binary [a])
Binary a => Dict (Binary [a])
forall (a :: Constraint). a => Dict a
Dict
instance Lifting NFData [] where lifting :: forall a. NFData a :- NFData [a]
lifting = (NFData a => Dict (NFData [a])) -> NFData a :- NFData [a]
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (NFData [a])
NFData a => Dict (NFData [a])
forall (a :: Constraint). a => Dict a
Dict

instance Lifting Eq Maybe where lifting :: forall a. Eq a :- Eq (Maybe a)
lifting = (Eq a => Dict (Eq (Maybe a))) -> Eq a :- Eq (Maybe a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Eq (Maybe a))
Eq a => Dict (Eq (Maybe a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Ord Maybe where lifting :: forall a. Ord a :- Ord (Maybe a)
lifting = (Ord a => Dict (Ord (Maybe a))) -> Ord a :- Ord (Maybe a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Ord (Maybe a))
Ord a => Dict (Ord (Maybe a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Show Maybe where lifting :: forall a. Show a :- Show (Maybe a)
lifting = (Show a => Dict (Show (Maybe a))) -> Show a :- Show (Maybe a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Show (Maybe a))
Show a => Dict (Show (Maybe a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Read Maybe where lifting :: forall a. Read a :- Read (Maybe a)
lifting = (Read a => Dict (Read (Maybe a))) -> Read a :- Read (Maybe a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Read (Maybe a))
Read a => Dict (Read (Maybe a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Hashable Maybe where lifting :: forall a. Hashable a :- Hashable (Maybe a)
lifting = (Hashable a => Dict (Hashable (Maybe a)))
-> Hashable a :- Hashable (Maybe a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Hashable (Maybe a))
Hashable a => Dict (Hashable (Maybe a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Binary Maybe where lifting :: forall a. Binary a :- Binary (Maybe a)
lifting = (Binary a => Dict (Binary (Maybe a)))
-> Binary a :- Binary (Maybe a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Binary (Maybe a))
Binary a => Dict (Binary (Maybe a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting NFData Maybe where lifting :: forall a. NFData a :- NFData (Maybe a)
lifting = (NFData a => Dict (NFData (Maybe a)))
-> NFData a :- NFData (Maybe a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (NFData (Maybe a))
NFData a => Dict (NFData (Maybe a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Semigroup Maybe where lifting :: forall a. Semigroup a :- Semigroup (Maybe a)
lifting = (Semigroup a => Dict (Semigroup (Maybe a)))
-> Semigroup a :- Semigroup (Maybe a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Semigroup (Maybe a))
Semigroup a => Dict (Semigroup (Maybe a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Monoid Maybe where lifting :: forall a. Monoid a :- Monoid (Maybe a)
lifting = (Monoid a => Dict (Monoid (Maybe a)))
-> Monoid a :- Monoid (Maybe a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Monoid (Maybe a))
Monoid a => Dict (Monoid (Maybe a))
forall (a :: Constraint). a => Dict a
Dict

instance Lifting Eq Ratio where lifting :: forall a. Eq a :- Eq (Ratio a)
lifting = (Eq a => Dict (Eq (Ratio a))) -> Eq a :- Eq (Ratio a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Eq (Ratio a))
Eq a => Dict (Eq (Ratio a))
forall (a :: Constraint). a => Dict a
Dict
-- instance Lifting Show Ratio where lifting = Sub Dict -- requires 7.10

instance Lifting Eq Complex where lifting :: forall a. Eq a :- Eq (Complex a)
lifting = (Eq a => Dict (Eq (Complex a))) -> Eq a :- Eq (Complex a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Eq (Complex a))
Eq a => Dict (Eq (Complex a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Read Complex where lifting :: forall a. Read a :- Read (Complex a)
lifting = (Read a => Dict (Read (Complex a))) -> Read a :- Read (Complex a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Read (Complex a))
Read a => Dict (Read (Complex a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Show Complex where lifting :: forall a. Show a :- Show (Complex a)
lifting = (Show a => Dict (Show (Complex a))) -> Show a :- Show (Complex a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Show (Complex a))
Show a => Dict (Show (Complex a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Semigroup ((->) a) where lifting :: forall a. Semigroup a :- Semigroup (a -> a)
lifting = (Semigroup a => Dict (Semigroup (a -> a)))
-> Semigroup a :- Semigroup (a -> a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Semigroup (a -> a))
Semigroup a => Dict (Semigroup (a -> a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Monoid ((->) a) where lifting :: forall a. Monoid a :- Monoid (a -> a)
lifting = (Monoid a => Dict (Monoid (a -> a))) -> Monoid a :- Monoid (a -> a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Monoid (a -> a))
Monoid a => Dict (Monoid (a -> a))
forall (a :: Constraint). a => Dict a
Dict

instance Eq a => Lifting Eq (Either a) where lifting :: forall a. Eq a :- Eq (Either a a)
lifting = (Eq a => Dict (Eq (Either a a))) -> Eq a :- Eq (Either a a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Eq (Either a a))
Eq a => Dict (Eq (Either a a))
forall (a :: Constraint). a => Dict a
Dict
instance Ord a => Lifting Ord (Either a) where lifting :: forall a. Ord a :- Ord (Either a a)
lifting = (Ord a => Dict (Ord (Either a a))) -> Ord a :- Ord (Either a a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Ord (Either a a))
Ord a => Dict (Ord (Either a a))
forall (a :: Constraint). a => Dict a
Dict
instance Show a => Lifting Show (Either a) where lifting :: forall a. Show a :- Show (Either a a)
lifting = (Show a => Dict (Show (Either a a))) -> Show a :- Show (Either a a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Show (Either a a))
Show a => Dict (Show (Either a a))
forall (a :: Constraint). a => Dict a
Dict
instance Read a => Lifting Read (Either a) where lifting :: forall a. Read a :- Read (Either a a)
lifting = (Read a => Dict (Read (Either a a))) -> Read a :- Read (Either a a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Read (Either a a))
Read a => Dict (Read (Either a a))
forall (a :: Constraint). a => Dict a
Dict
instance Hashable a => Lifting Hashable (Either a) where lifting :: forall a. Hashable a :- Hashable (Either a a)
lifting = (Hashable a => Dict (Hashable (Either a a)))
-> Hashable a :- Hashable (Either a a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Hashable (Either a a))
Hashable a => Dict (Hashable (Either a a))
forall (a :: Constraint). a => Dict a
Dict
instance Binary a => Lifting Binary (Either a) where lifting :: forall a. Binary a :- Binary (Either a a)
lifting = (Binary a => Dict (Binary (Either a a)))
-> Binary a :- Binary (Either a a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Binary (Either a a))
Binary a => Dict (Binary (Either a a))
forall (a :: Constraint). a => Dict a
Dict
instance NFData a => Lifting NFData (Either a) where lifting :: forall a. NFData a :- NFData (Either a a)
lifting = (NFData a => Dict (NFData (Either a a)))
-> NFData a :- NFData (Either a a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (NFData (Either a a))
NFData a => Dict (NFData (Either a a))
forall (a :: Constraint). a => Dict a
Dict

instance Eq a => Lifting Eq ((,) a) where lifting :: forall a. Eq a :- Eq (a, a)
lifting = (Eq a => Dict (Eq (a, a))) -> Eq a :- Eq (a, a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Eq (a, a))
Eq a => Dict (Eq (a, a))
forall (a :: Constraint). a => Dict a
Dict
instance Ord a => Lifting Ord ((,) a) where lifting :: forall a. Ord a :- Ord (a, a)
lifting = (Ord a => Dict (Ord (a, a))) -> Ord a :- Ord (a, a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Ord (a, a))
Ord a => Dict (Ord (a, a))
forall (a :: Constraint). a => Dict a
Dict
instance Show a => Lifting Show ((,) a) where lifting :: forall a. Show a :- Show (a, a)
lifting = (Show a => Dict (Show (a, a))) -> Show a :- Show (a, a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Show (a, a))
Show a => Dict (Show (a, a))
forall (a :: Constraint). a => Dict a
Dict
instance Read a => Lifting Read ((,) a) where lifting :: forall a. Read a :- Read (a, a)
lifting = (Read a => Dict (Read (a, a))) -> Read a :- Read (a, a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Read (a, a))
Read a => Dict (Read (a, a))
forall (a :: Constraint). a => Dict a
Dict
instance Hashable a => Lifting Hashable ((,) a) where lifting :: forall a. Hashable a :- Hashable (a, a)
lifting = (Hashable a => Dict (Hashable (a, a)))
-> Hashable a :- Hashable (a, a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Hashable (a, a))
Hashable a => Dict (Hashable (a, a))
forall (a :: Constraint). a => Dict a
Dict
instance Binary a => Lifting Binary ((,) a) where lifting :: forall a. Binary a :- Binary (a, a)
lifting = (Binary a => Dict (Binary (a, a))) -> Binary a :- Binary (a, a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Binary (a, a))
Binary a => Dict (Binary (a, a))
forall (a :: Constraint). a => Dict a
Dict
instance NFData a => Lifting NFData ((,) a) where lifting :: forall a. NFData a :- NFData (a, a)
lifting = (NFData a => Dict (NFData (a, a))) -> NFData a :- NFData (a, a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (NFData (a, a))
NFData a => Dict (NFData (a, a))
forall (a :: Constraint). a => Dict a
Dict
instance Semigroup a => Lifting Semigroup ((,) a) where lifting :: forall a. Semigroup a :- Semigroup (a, a)
lifting = (Semigroup a => Dict (Semigroup (a, a)))
-> Semigroup a :- Semigroup (a, a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Semigroup (a, a))
Semigroup a => Dict (Semigroup (a, a))
forall (a :: Constraint). a => Dict a
Dict
instance Monoid a => Lifting Monoid ((,) a) where lifting :: forall a. Monoid a :- Monoid (a, a)
lifting = (Monoid a => Dict (Monoid (a, a))) -> Monoid a :- Monoid (a, a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Monoid (a, a))
Monoid a => Dict (Monoid (a, a))
forall (a :: Constraint). a => Dict a
Dict
instance Bounded a => Lifting Bounded ((,) a) where lifting :: forall a. Bounded a :- Bounded (a, a)
lifting = (Bounded a => Dict (Bounded (a, a))) -> Bounded a :- Bounded (a, a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Bounded (a, a))
Bounded a => Dict (Bounded (a, a))
forall (a :: Constraint). a => Dict a
Dict
instance Ix a => Lifting Ix ((,) a) where lifting :: forall a. Ix a :- Ix (a, a)
lifting = (Ix a => Dict (Ix (a, a))) -> Ix a :- Ix (a, a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Ix (a, a))
Ix a => Dict (Ix (a, a))
forall (a :: Constraint). a => Dict a
Dict

instance Functor f => Lifting Functor (Compose f) where lifting :: forall (a :: * -> *). Functor a :- Functor (Compose f a)
lifting = (Functor a => Dict (Functor (Compose f a)))
-> Functor a :- Functor (Compose f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Functor (Compose f a))
Functor a => Dict (Functor (Compose f a))
forall (a :: Constraint). a => Dict a
Dict
instance Foldable f => Lifting Foldable (Compose f) where lifting :: forall (a :: * -> *). Foldable a :- Foldable (Compose f a)
lifting = (Foldable a => Dict (Foldable (Compose f a)))
-> Foldable a :- Foldable (Compose f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Foldable (Compose f a))
Foldable a => Dict (Foldable (Compose f a))
forall (a :: Constraint). a => Dict a
Dict
instance Traversable f => Lifting Traversable (Compose f) where lifting :: forall (a :: * -> *). Traversable a :- Traversable (Compose f a)
lifting = (Traversable a => Dict (Traversable (Compose f a)))
-> Traversable a :- Traversable (Compose f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Traversable (Compose f a))
Traversable a => Dict (Traversable (Compose f a))
forall (a :: Constraint). a => Dict a
Dict
instance Applicative f => Lifting Applicative (Compose f) where lifting :: forall (a :: * -> *). Applicative a :- Applicative (Compose f a)
lifting = (Applicative a => Dict (Applicative (Compose f a)))
-> Applicative a :- Applicative (Compose f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Applicative (Compose f a))
Applicative a => Dict (Applicative (Compose f a))
forall (a :: Constraint). a => Dict a
Dict
instance Alternative f => Lifting Alternative (Compose f) where lifting :: forall (a :: * -> *). Alternative a :- Alternative (Compose f a)
lifting = (Alternative a => Dict (Alternative (Compose f a)))
-> Alternative a :- Alternative (Compose f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Alternative (Compose f a))
Alternative a => Dict (Alternative (Compose f a))
forall (a :: Constraint). a => Dict a
Dict -- overconstrained

instance Show1 f => Lifting Show1 (Compose f) where lifting :: forall (a :: * -> *). Show1 a :- Show1 (Compose f a)
lifting = (Show1 a => Dict (Show1 (Compose f a)))
-> Show1 a :- Show1 (Compose f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Show1 (Compose f a))
Show1 a => Dict (Show1 (Compose f a))
forall (a :: Constraint). a => Dict a
Dict
instance Eq1 f => Lifting Eq1 (Compose f) where lifting :: forall (a :: * -> *). Eq1 a :- Eq1 (Compose f a)
lifting = (Eq1 a => Dict (Eq1 (Compose f a))) -> Eq1 a :- Eq1 (Compose f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Eq1 (Compose f a))
Eq1 a => Dict (Eq1 (Compose f a))
forall (a :: Constraint). a => Dict a
Dict
instance Ord1 f => Lifting Ord1 (Compose f) where lifting :: forall (a :: * -> *). Ord1 a :- Ord1 (Compose f a)
lifting = (Ord1 a => Dict (Ord1 (Compose f a)))
-> Ord1 a :- Ord1 (Compose f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Ord1 (Compose f a))
Ord1 a => Dict (Ord1 (Compose f a))
forall (a :: Constraint). a => Dict a
Dict
instance Read1 f => Lifting Read1 (Compose f) where lifting :: forall (a :: * -> *). Read1 a :- Read1 (Compose f a)
lifting = (Read1 a => Dict (Read1 (Compose f a)))
-> Read1 a :- Read1 (Compose f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Read1 (Compose f a))
Read1 a => Dict (Read1 (Compose f a))
forall (a :: Constraint). a => Dict a
Dict
instance (Eq1 f, Eq1 g) => Lifting Eq (Compose f g) where lifting :: forall a. Eq a :- Eq (Compose f g a)
lifting = (Eq a => Dict (Eq (Compose f g a))) -> Eq a :- Eq (Compose f g a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Eq (Compose f g a))
Eq a => Dict (Eq (Compose f g a))
forall (a :: Constraint). a => Dict a
Dict
instance (Ord1 f, Ord1 g) => Lifting Ord (Compose f g) where lifting :: forall a. Ord a :- Ord (Compose f g a)
lifting = (Ord a => Dict (Ord (Compose f g a)))
-> Ord a :- Ord (Compose f g a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Ord (Compose f g a))
Ord a => Dict (Ord (Compose f g a))
forall (a :: Constraint). a => Dict a
Dict
instance (Read1 f, Read1 g) => Lifting Read (Compose f g) where lifting :: forall a. Read a :- Read (Compose f g a)
lifting = (Read a => Dict (Read (Compose f g a)))
-> Read a :- Read (Compose f g a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Read (Compose f g a))
Read a => Dict (Read (Compose f g a))
forall (a :: Constraint). a => Dict a
Dict
instance (Show1 f, Show1 g) => Lifting Show (Compose f g) where lifting :: forall a. Show a :- Show (Compose f g a)
lifting = (Show a => Dict (Show (Compose f g a)))
-> Show a :- Show (Compose f g a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Show (Compose f g a))
Show a => Dict (Show (Compose f g a))
forall (a :: Constraint). a => Dict a
Dict

instance Functor f => Lifting Functor (Functor.Product f) where lifting :: forall (a :: * -> *). Functor a :- Functor (Product f a)
lifting = (Functor a => Dict (Functor (Product f a)))
-> Functor a :- Functor (Product f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Functor (Product f a))
Functor a => Dict (Functor (Product f a))
forall (a :: Constraint). a => Dict a
Dict
instance Foldable f => Lifting Foldable (Functor.Product f) where lifting :: forall (a :: * -> *). Foldable a :- Foldable (Product f a)
lifting = (Foldable a => Dict (Foldable (Product f a)))
-> Foldable a :- Foldable (Product f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Foldable (Product f a))
Foldable a => Dict (Foldable (Product f a))
forall (a :: Constraint). a => Dict a
Dict
instance Traversable f => Lifting Traversable (Functor.Product f) where lifting :: forall (a :: * -> *). Traversable a :- Traversable (Product f a)
lifting = (Traversable a => Dict (Traversable (Product f a)))
-> Traversable a :- Traversable (Product f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Traversable (Product f a))
Traversable a => Dict (Traversable (Product f a))
forall (a :: Constraint). a => Dict a
Dict
instance Applicative f => Lifting Applicative (Functor.Product f) where lifting :: forall (a :: * -> *). Applicative a :- Applicative (Product f a)
lifting = (Applicative a => Dict (Applicative (Product f a)))
-> Applicative a :- Applicative (Product f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Applicative (Product f a))
Applicative a => Dict (Applicative (Product f a))
forall (a :: Constraint). a => Dict a
Dict
instance Alternative f => Lifting Alternative (Functor.Product f) where lifting :: forall (a :: * -> *). Alternative a :- Alternative (Product f a)
lifting = (Alternative a => Dict (Alternative (Product f a)))
-> Alternative a :- Alternative (Product f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Alternative (Product f a))
Alternative a => Dict (Alternative (Product f a))
forall (a :: Constraint). a => Dict a
Dict
instance Monad f => Lifting Monad (Functor.Product f) where lifting :: forall (a :: * -> *). Monad a :- Monad (Product f a)
lifting = (Monad a => Dict (Monad (Product f a)))
-> Monad a :- Monad (Product f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Monad (Product f a))
Monad a => Dict (Monad (Product f a))
forall (a :: Constraint). a => Dict a
Dict
instance MonadFix f => Lifting MonadFix (Functor.Product f) where lifting :: forall (a :: * -> *). MonadFix a :- MonadFix (Product f a)
lifting = (MonadFix a => Dict (MonadFix (Product f a)))
-> MonadFix a :- MonadFix (Product f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadFix (Product f a))
MonadFix a => Dict (MonadFix (Product f a))
forall (a :: Constraint). a => Dict a
Dict
instance MonadPlus f => Lifting MonadPlus (Functor.Product f) where lifting :: forall (a :: * -> *). MonadPlus a :- MonadPlus (Product f a)
lifting = (MonadPlus a => Dict (MonadPlus (Product f a)))
-> MonadPlus a :- MonadPlus (Product f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadPlus (Product f a))
MonadPlus a => Dict (MonadPlus (Product f a))
forall (a :: Constraint). a => Dict a
Dict
instance Show1 f => Lifting Show1 (Functor.Product f) where lifting :: forall (a :: * -> *). Show1 a :- Show1 (Product f a)
lifting = (Show1 a => Dict (Show1 (Product f a)))
-> Show1 a :- Show1 (Product f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Show1 (Product f a))
Show1 a => Dict (Show1 (Product f a))
forall (a :: Constraint). a => Dict a
Dict
instance Eq1 f => Lifting Eq1 (Functor.Product f) where lifting :: forall (a :: * -> *). Eq1 a :- Eq1 (Product f a)
lifting = (Eq1 a => Dict (Eq1 (Product f a))) -> Eq1 a :- Eq1 (Product f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Eq1 (Product f a))
Eq1 a => Dict (Eq1 (Product f a))
forall (a :: Constraint). a => Dict a
Dict
instance Ord1 f => Lifting Ord1 (Functor.Product f) where lifting :: forall (a :: * -> *). Ord1 a :- Ord1 (Product f a)
lifting = (Ord1 a => Dict (Ord1 (Product f a)))
-> Ord1 a :- Ord1 (Product f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Ord1 (Product f a))
Ord1 a => Dict (Ord1 (Product f a))
forall (a :: Constraint). a => Dict a
Dict
instance Read1 f => Lifting Read1 (Functor.Product f) where lifting :: forall (a :: * -> *). Read1 a :- Read1 (Product f a)
lifting = (Read1 a => Dict (Read1 (Product f a)))
-> Read1 a :- Read1 (Product f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Read1 (Product f a))
Read1 a => Dict (Read1 (Product f a))
forall (a :: Constraint). a => Dict a
Dict
instance (Eq1 f, Eq1 g) => Lifting Eq (Functor.Product f g) where lifting :: forall a. Eq a :- Eq (Product f g a)
lifting = (Eq a => Dict (Eq (Product f g a))) -> Eq a :- Eq (Product f g a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Eq (Product f g a))
Eq a => Dict (Eq (Product f g a))
forall (a :: Constraint). a => Dict a
Dict
instance (Ord1 f, Ord1 g) => Lifting Ord (Functor.Product f g) where lifting :: forall a. Ord a :- Ord (Product f g a)
lifting = (Ord a => Dict (Ord (Product f g a)))
-> Ord a :- Ord (Product f g a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Ord (Product f g a))
Ord a => Dict (Ord (Product f g a))
forall (a :: Constraint). a => Dict a
Dict
instance (Read1 f, Read1 g) => Lifting Read (Functor.Product f g) where lifting :: forall a. Read a :- Read (Product f g a)
lifting = (Read a => Dict (Read (Product f g a)))
-> Read a :- Read (Product f g a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Read (Product f g a))
Read a => Dict (Read (Product f g a))
forall (a :: Constraint). a => Dict a
Dict
instance (Show1 f, Show1 g) => Lifting Show (Functor.Product f g) where lifting :: forall a. Show a :- Show (Product f g a)
lifting = (Show a => Dict (Show (Product f g a)))
-> Show a :- Show (Product f g a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Show (Product f g a))
Show a => Dict (Show (Product f g a))
forall (a :: Constraint). a => Dict a
Dict

instance Functor f => Lifting Functor (Functor.Sum f) where lifting :: forall (a :: * -> *). Functor a :- Functor (Sum f a)
lifting = (Functor a => Dict (Functor (Sum f a)))
-> Functor a :- Functor (Sum f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Functor (Sum f a))
Functor a => Dict (Functor (Sum f a))
forall (a :: Constraint). a => Dict a
Dict
instance Foldable f => Lifting Foldable (Functor.Sum f) where lifting :: forall (a :: * -> *). Foldable a :- Foldable (Sum f a)
lifting = (Foldable a => Dict (Foldable (Sum f a)))
-> Foldable a :- Foldable (Sum f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Foldable (Sum f a))
Foldable a => Dict (Foldable (Sum f a))
forall (a :: Constraint). a => Dict a
Dict
instance Traversable f => Lifting Traversable (Functor.Sum f) where lifting :: forall (a :: * -> *). Traversable a :- Traversable (Sum f a)
lifting = (Traversable a => Dict (Traversable (Sum f a)))
-> Traversable a :- Traversable (Sum f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Traversable (Sum f a))
Traversable a => Dict (Traversable (Sum f a))
forall (a :: Constraint). a => Dict a
Dict
instance Show1 f => Lifting Show1 (Functor.Sum f) where lifting :: forall (a :: * -> *). Show1 a :- Show1 (Sum f a)
lifting = (Show1 a => Dict (Show1 (Sum f a))) -> Show1 a :- Show1 (Sum f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Show1 (Sum f a))
Show1 a => Dict (Show1 (Sum f a))
forall (a :: Constraint). a => Dict a
Dict
instance Eq1 f => Lifting Eq1 (Functor.Sum f) where lifting :: forall (a :: * -> *). Eq1 a :- Eq1 (Sum f a)
lifting = (Eq1 a => Dict (Eq1 (Sum f a))) -> Eq1 a :- Eq1 (Sum f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Eq1 (Sum f a))
Eq1 a => Dict (Eq1 (Sum f a))
forall (a :: Constraint). a => Dict a
Dict
instance Ord1 f => Lifting Ord1 (Functor.Sum f) where lifting :: forall (a :: * -> *). Ord1 a :- Ord1 (Sum f a)
lifting = (Ord1 a => Dict (Ord1 (Sum f a))) -> Ord1 a :- Ord1 (Sum f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Ord1 (Sum f a))
Ord1 a => Dict (Ord1 (Sum f a))
forall (a :: Constraint). a => Dict a
Dict
instance Read1 f => Lifting Read1 (Functor.Sum f) where lifting :: forall (a :: * -> *). Read1 a :- Read1 (Sum f a)
lifting = (Read1 a => Dict (Read1 (Sum f a))) -> Read1 a :- Read1 (Sum f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Read1 (Sum f a))
Read1 a => Dict (Read1 (Sum f a))
forall (a :: Constraint). a => Dict a
Dict
instance (Eq1 f, Eq1 g) => Lifting Eq (Functor.Sum f g) where lifting :: forall a. Eq a :- Eq (Sum f g a)
lifting = (Eq a => Dict (Eq (Sum f g a))) -> Eq a :- Eq (Sum f g a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Eq (Sum f g a))
Eq a => Dict (Eq (Sum f g a))
forall (a :: Constraint). a => Dict a
Dict
instance (Ord1 f, Ord1 g) => Lifting Ord (Functor.Sum f g) where lifting :: forall a. Ord a :- Ord (Sum f g a)
lifting = (Ord a => Dict (Ord (Sum f g a))) -> Ord a :- Ord (Sum f g a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Ord (Sum f g a))
Ord a => Dict (Ord (Sum f g a))
forall (a :: Constraint). a => Dict a
Dict
instance (Read1 f, Read1 g) => Lifting Read (Functor.Sum f g) where lifting :: forall a. Read a :- Read (Sum f g a)
lifting = (Read a => Dict (Read (Sum f g a))) -> Read a :- Read (Sum f g a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Read (Sum f g a))
Read a => Dict (Read (Sum f g a))
forall (a :: Constraint). a => Dict a
Dict
instance (Show1 f, Show1 g) => Lifting Show (Functor.Sum f g) where lifting :: forall a. Show a :- Show (Sum f g a)
lifting = (Show a => Dict (Show (Sum f g a))) -> Show a :- Show (Sum f g a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Show (Sum f g a))
Show a => Dict (Show (Sum f g a))
forall (a :: Constraint). a => Dict a
Dict

instance Lifting Functor (Strict.StateT s) where lifting :: forall (a :: * -> *). Functor a :- Functor (StateT s a)
lifting = (Functor a => Dict (Functor (StateT s a)))
-> Functor a :- Functor (StateT s a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Functor (StateT s a))
Functor a => Dict (Functor (StateT s a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Monad (Strict.StateT s) where lifting :: forall (a :: * -> *). Monad a :- Monad (StateT s a)
lifting = (Monad a => Dict (Monad (StateT s a)))
-> Monad a :- Monad (StateT s a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Monad (StateT s a))
Monad a => Dict (Monad (StateT s a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting MonadFix (Strict.StateT s) where lifting :: forall (a :: * -> *). MonadFix a :- MonadFix (StateT s a)
lifting = (MonadFix a => Dict (MonadFix (StateT s a)))
-> MonadFix a :- MonadFix (StateT s a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadFix (StateT s a))
MonadFix a => Dict (MonadFix (StateT s a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting MonadIO (Strict.StateT s) where lifting :: forall (a :: * -> *). MonadIO a :- MonadIO (StateT s a)
lifting = (MonadIO a => Dict (MonadIO (StateT s a)))
-> MonadIO a :- MonadIO (StateT s a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadIO (StateT s a))
MonadIO a => Dict (MonadIO (StateT s a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting MonadPlus (Strict.StateT s) where lifting :: forall (a :: * -> *). MonadPlus a :- MonadPlus (StateT s a)
lifting = (MonadPlus a => Dict (MonadPlus (StateT s a)))
-> MonadPlus a :- MonadPlus (StateT s a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadPlus (StateT s a))
MonadPlus a => Dict (MonadPlus (StateT s a))
forall (a :: Constraint). a => Dict a
Dict

instance Lifting Functor (Lazy.StateT s) where lifting :: forall (a :: * -> *). Functor a :- Functor (StateT s a)
lifting = (Functor a => Dict (Functor (StateT s a)))
-> Functor a :- Functor (StateT s a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Functor (StateT s a))
Functor a => Dict (Functor (StateT s a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Monad (Lazy.StateT s) where lifting :: forall (a :: * -> *). Monad a :- Monad (StateT s a)
lifting = (Monad a => Dict (Monad (StateT s a)))
-> Monad a :- Monad (StateT s a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Monad (StateT s a))
Monad a => Dict (Monad (StateT s a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting MonadFix (Lazy.StateT s) where lifting :: forall (a :: * -> *). MonadFix a :- MonadFix (StateT s a)
lifting = (MonadFix a => Dict (MonadFix (StateT s a)))
-> MonadFix a :- MonadFix (StateT s a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadFix (StateT s a))
MonadFix a => Dict (MonadFix (StateT s a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting MonadIO (Lazy.StateT s) where lifting :: forall (a :: * -> *). MonadIO a :- MonadIO (StateT s a)
lifting = (MonadIO a => Dict (MonadIO (StateT s a)))
-> MonadIO a :- MonadIO (StateT s a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadIO (StateT s a))
MonadIO a => Dict (MonadIO (StateT s a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting MonadPlus (Lazy.StateT s) where lifting :: forall (a :: * -> *). MonadPlus a :- MonadPlus (StateT s a)
lifting = (MonadPlus a => Dict (MonadPlus (StateT s a)))
-> MonadPlus a :- MonadPlus (StateT s a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadPlus (StateT s a))
MonadPlus a => Dict (MonadPlus (StateT s a))
forall (a :: Constraint). a => Dict a
Dict

instance Lifting Functor (Lazy.RWST r w s) where lifting :: forall (a :: * -> *). Functor a :- Functor (RWST r w s a)
lifting = (Functor a => Dict (Functor (RWST r w s a)))
-> Functor a :- Functor (RWST r w s a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Functor (RWST r w s a))
Functor a => Dict (Functor (RWST r w s a))
forall (a :: Constraint). a => Dict a
Dict
instance Monoid w => Lifting Monad (Lazy.RWST r w s) where lifting :: forall (a :: * -> *). Monad a :- Monad (RWST r w s a)
lifting = (Monad a => Dict (Monad (RWST r w s a)))
-> Monad a :- Monad (RWST r w s a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Monad (RWST r w s a))
Monad a => Dict (Monad (RWST r w s a))
forall (a :: Constraint). a => Dict a
Dict
instance Monoid w => Lifting MonadFix (Lazy.RWST r w s) where lifting :: forall (a :: * -> *). MonadFix a :- MonadFix (RWST r w s a)
lifting = (MonadFix a => Dict (MonadFix (RWST r w s a)))
-> MonadFix a :- MonadFix (RWST r w s a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadFix (RWST r w s a))
MonadFix a => Dict (MonadFix (RWST r w s a))
forall (a :: Constraint). a => Dict a
Dict
instance Monoid w => Lifting MonadPlus (Lazy.RWST r w s) where lifting :: forall (a :: * -> *). MonadPlus a :- MonadPlus (RWST r w s a)
lifting = (MonadPlus a => Dict (MonadPlus (RWST r w s a)))
-> MonadPlus a :- MonadPlus (RWST r w s a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadPlus (RWST r w s a))
MonadPlus a => Dict (MonadPlus (RWST r w s a))
forall (a :: Constraint). a => Dict a
Dict
instance Monoid w => Lifting MonadIO (Lazy.RWST r w s) where lifting :: forall (a :: * -> *). MonadIO a :- MonadIO (RWST r w s a)
lifting = (MonadIO a => Dict (MonadIO (RWST r w s a)))
-> MonadIO a :- MonadIO (RWST r w s a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadIO (RWST r w s a))
MonadIO a => Dict (MonadIO (RWST r w s a))
forall (a :: Constraint). a => Dict a
Dict

instance Lifting Functor (Strict.RWST r w s) where lifting :: forall (a :: * -> *). Functor a :- Functor (RWST r w s a)
lifting = (Functor a => Dict (Functor (RWST r w s a)))
-> Functor a :- Functor (RWST r w s a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Functor (RWST r w s a))
Functor a => Dict (Functor (RWST r w s a))
forall (a :: Constraint). a => Dict a
Dict
instance Monoid w => Lifting Monad (Strict.RWST r w s) where lifting :: forall (a :: * -> *). Monad a :- Monad (RWST r w s a)
lifting = (Monad a => Dict (Monad (RWST r w s a)))
-> Monad a :- Monad (RWST r w s a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Monad (RWST r w s a))
Monad a => Dict (Monad (RWST r w s a))
forall (a :: Constraint). a => Dict a
Dict
instance Monoid w => Lifting MonadFix (Strict.RWST r w s) where lifting :: forall (a :: * -> *). MonadFix a :- MonadFix (RWST r w s a)
lifting = (MonadFix a => Dict (MonadFix (RWST r w s a)))
-> MonadFix a :- MonadFix (RWST r w s a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadFix (RWST r w s a))
MonadFix a => Dict (MonadFix (RWST r w s a))
forall (a :: Constraint). a => Dict a
Dict
instance Monoid w => Lifting MonadPlus (Strict.RWST r w s) where lifting :: forall (a :: * -> *). MonadPlus a :- MonadPlus (RWST r w s a)
lifting = (MonadPlus a => Dict (MonadPlus (RWST r w s a)))
-> MonadPlus a :- MonadPlus (RWST r w s a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadPlus (RWST r w s a))
MonadPlus a => Dict (MonadPlus (RWST r w s a))
forall (a :: Constraint). a => Dict a
Dict
instance Monoid w => Lifting MonadIO (Strict.RWST r w s) where lifting :: forall (a :: * -> *). MonadIO a :- MonadIO (RWST r w s a)
lifting = (MonadIO a => Dict (MonadIO (RWST r w s a)))
-> MonadIO a :- MonadIO (RWST r w s a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadIO (RWST r w s a))
MonadIO a => Dict (MonadIO (RWST r w s a))
forall (a :: Constraint). a => Dict a
Dict

instance Lifting Functor (ReaderT e) where lifting :: forall (a :: * -> *). Functor a :- Functor (ReaderT e a)
lifting = (Functor a => Dict (Functor (ReaderT e a)))
-> Functor a :- Functor (ReaderT e a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Functor (ReaderT e a))
Functor a => Dict (Functor (ReaderT e a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Applicative (ReaderT e) where lifting :: forall (a :: * -> *). Applicative a :- Applicative (ReaderT e a)
lifting = (Applicative a => Dict (Applicative (ReaderT e a)))
-> Applicative a :- Applicative (ReaderT e a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Applicative (ReaderT e a))
Applicative a => Dict (Applicative (ReaderT e a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Alternative (ReaderT e) where lifting :: forall (a :: * -> *). Alternative a :- Alternative (ReaderT e a)
lifting = (Alternative a => Dict (Alternative (ReaderT e a)))
-> Alternative a :- Alternative (ReaderT e a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Alternative (ReaderT e a))
Alternative a => Dict (Alternative (ReaderT e a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Monad (ReaderT e) where lifting :: forall (a :: * -> *). Monad a :- Monad (ReaderT e a)
lifting = (Monad a => Dict (Monad (ReaderT e a)))
-> Monad a :- Monad (ReaderT e a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Monad (ReaderT e a))
Monad a => Dict (Monad (ReaderT e a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting MonadPlus (ReaderT e) where lifting :: forall (a :: * -> *). MonadPlus a :- MonadPlus (ReaderT e a)
lifting = (MonadPlus a => Dict (MonadPlus (ReaderT e a)))
-> MonadPlus a :- MonadPlus (ReaderT e a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadPlus (ReaderT e a))
MonadPlus a => Dict (MonadPlus (ReaderT e a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting MonadFix (ReaderT e) where lifting :: forall (a :: * -> *). MonadFix a :- MonadFix (ReaderT e a)
lifting = (MonadFix a => Dict (MonadFix (ReaderT e a)))
-> MonadFix a :- MonadFix (ReaderT e a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadFix (ReaderT e a))
MonadFix a => Dict (MonadFix (ReaderT e a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting MonadIO (ReaderT e) where lifting :: forall (a :: * -> *). MonadIO a :- MonadIO (ReaderT e a)
lifting = (MonadIO a => Dict (MonadIO (ReaderT e a)))
-> MonadIO a :- MonadIO (ReaderT e a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadIO (ReaderT e a))
MonadIO a => Dict (MonadIO (ReaderT e a))
forall (a :: Constraint). a => Dict a
Dict

instance Lifting Functor (ExceptT e) where lifting :: forall (a :: * -> *). Functor a :- Functor (ExceptT e a)
lifting = (Functor a => Dict (Functor (ExceptT e a)))
-> Functor a :- Functor (ExceptT e a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Functor (ExceptT e a))
Functor a => Dict (Functor (ExceptT e a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Foldable (ExceptT e) where lifting :: forall (a :: * -> *). Foldable a :- Foldable (ExceptT e a)
lifting = (Foldable a => Dict (Foldable (ExceptT e a)))
-> Foldable a :- Foldable (ExceptT e a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Foldable (ExceptT e a))
Foldable a => Dict (Foldable (ExceptT e a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Traversable (ExceptT e) where lifting :: forall (a :: * -> *). Traversable a :- Traversable (ExceptT e a)
lifting = (Traversable a => Dict (Traversable (ExceptT e a)))
-> Traversable a :- Traversable (ExceptT e a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Traversable (ExceptT e a))
Traversable a => Dict (Traversable (ExceptT e a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Monad (ExceptT e) where lifting :: forall (a :: * -> *). Monad a :- Monad (ExceptT e a)
lifting = (Monad a => Dict (Monad (ExceptT e a)))
-> Monad a :- Monad (ExceptT e a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Monad (ExceptT e a))
Monad a => Dict (Monad (ExceptT e a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting MonadFix (ExceptT e) where lifting :: forall (a :: * -> *). MonadFix a :- MonadFix (ExceptT e a)
lifting = (MonadFix a => Dict (MonadFix (ExceptT e a)))
-> MonadFix a :- MonadFix (ExceptT e a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadFix (ExceptT e a))
MonadFix a => Dict (MonadFix (ExceptT e a))
forall (a :: Constraint). a => Dict a
Dict
instance Monoid e => Lifting MonadPlus (ExceptT e) where lifting :: forall (a :: * -> *). MonadPlus a :- MonadPlus (ExceptT e a)
lifting = (MonadPlus a => Dict (MonadPlus (ExceptT e a)))
-> MonadPlus a :- MonadPlus (ExceptT e a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadPlus (ExceptT e a))
MonadPlus a => Dict (MonadPlus (ExceptT e a))
forall (a :: Constraint). a => Dict a
Dict -- overconstrained!
instance Lifting MonadIO (ExceptT e) where lifting :: forall (a :: * -> *). MonadIO a :- MonadIO (ExceptT e a)
lifting = (MonadIO a => Dict (MonadIO (ExceptT e a)))
-> MonadIO a :- MonadIO (ExceptT e a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadIO (ExceptT e a))
MonadIO a => Dict (MonadIO (ExceptT e a))
forall (a :: Constraint). a => Dict a
Dict
instance Show e => Lifting Show1 (ExceptT e) where lifting :: forall (a :: * -> *). Show1 a :- Show1 (ExceptT e a)
lifting = (Show1 a => Dict (Show1 (ExceptT e a)))
-> Show1 a :- Show1 (ExceptT e a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Show1 (ExceptT e a))
Show1 a => Dict (Show1 (ExceptT e a))
forall (a :: Constraint). a => Dict a
Dict
instance Eq e => Lifting Eq1 (ExceptT e) where lifting :: forall (a :: * -> *). Eq1 a :- Eq1 (ExceptT e a)
lifting = (Eq1 a => Dict (Eq1 (ExceptT e a))) -> Eq1 a :- Eq1 (ExceptT e a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Eq1 (ExceptT e a))
Eq1 a => Dict (Eq1 (ExceptT e a))
forall (a :: Constraint). a => Dict a
Dict
instance Ord e => Lifting Ord1 (ExceptT e) where lifting :: forall (a :: * -> *). Ord1 a :- Ord1 (ExceptT e a)
lifting = (Ord1 a => Dict (Ord1 (ExceptT e a)))
-> Ord1 a :- Ord1 (ExceptT e a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Ord1 (ExceptT e a))
Ord1 a => Dict (Ord1 (ExceptT e a))
forall (a :: Constraint). a => Dict a
Dict
instance Read e => Lifting Read1 (ExceptT e) where lifting :: forall (a :: * -> *). Read1 a :- Read1 (ExceptT e a)
lifting = (Read1 a => Dict (Read1 (ExceptT e a)))
-> Read1 a :- Read1 (ExceptT e a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Read1 (ExceptT e a))
Read1 a => Dict (Read1 (ExceptT e a))
forall (a :: Constraint). a => Dict a
Dict
instance (Show e, Show1 m) => Lifting Show (ExceptT e m) where lifting :: forall a. Show a :- Show (ExceptT e m a)
lifting = (Show a => Dict (Show (ExceptT e m a)))
-> Show a :- Show (ExceptT e m a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Show (ExceptT e m a))
Show a => Dict (Show (ExceptT e m a))
forall (a :: Constraint). a => Dict a
Dict
instance (Eq e, Eq1 m) => Lifting Eq (ExceptT e m) where lifting :: forall a. Eq a :- Eq (ExceptT e m a)
lifting = (Eq a => Dict (Eq (ExceptT e m a))) -> Eq a :- Eq (ExceptT e m a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Eq (ExceptT e m a))
Eq a => Dict (Eq (ExceptT e m a))
forall (a :: Constraint). a => Dict a
Dict
instance (Ord e, Ord1 m) => Lifting Ord (ExceptT e m) where lifting :: forall a. Ord a :- Ord (ExceptT e m a)
lifting = (Ord a => Dict (Ord (ExceptT e m a)))
-> Ord a :- Ord (ExceptT e m a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Ord (ExceptT e m a))
Ord a => Dict (Ord (ExceptT e m a))
forall (a :: Constraint). a => Dict a
Dict
instance (Read e, Read1 m) => Lifting Read (ExceptT e m) where lifting :: forall a. Read a :- Read (ExceptT e m a)
lifting = (Read a => Dict (Read (ExceptT e m a)))
-> Read a :- Read (ExceptT e m a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Read (ExceptT e m a))
Read a => Dict (Read (ExceptT e m a))
forall (a :: Constraint). a => Dict a
Dict

instance Lifting Functor (Strict.WriterT w) where lifting :: forall (a :: * -> *). Functor a :- Functor (WriterT w a)
lifting = (Functor a => Dict (Functor (WriterT w a)))
-> Functor a :- Functor (WriterT w a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Functor (WriterT w a))
Functor a => Dict (Functor (WriterT w a))
forall (a :: Constraint). a => Dict a
Dict
instance Monoid w => Lifting Applicative (Strict.WriterT w) where lifting :: forall (a :: * -> *). Applicative a :- Applicative (WriterT w a)
lifting = (Applicative a => Dict (Applicative (WriterT w a)))
-> Applicative a :- Applicative (WriterT w a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Applicative (WriterT w a))
Applicative a => Dict (Applicative (WriterT w a))
forall (a :: Constraint). a => Dict a
Dict
instance Monoid w => Lifting Alternative (Strict.WriterT w) where lifting :: forall (a :: * -> *). Alternative a :- Alternative (WriterT w a)
lifting = (Alternative a => Dict (Alternative (WriterT w a)))
-> Alternative a :- Alternative (WriterT w a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Alternative (WriterT w a))
Alternative a => Dict (Alternative (WriterT w a))
forall (a :: Constraint). a => Dict a
Dict
instance Monoid w => Lifting Monad (Strict.WriterT w) where lifting :: forall (a :: * -> *). Monad a :- Monad (WriterT w a)
lifting = (Monad a => Dict (Monad (WriterT w a)))
-> Monad a :- Monad (WriterT w a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Monad (WriterT w a))
Monad a => Dict (Monad (WriterT w a))
forall (a :: Constraint). a => Dict a
Dict
instance Monoid w => Lifting MonadFix (Strict.WriterT w) where lifting :: forall (a :: * -> *). MonadFix a :- MonadFix (WriterT w a)
lifting = (MonadFix a => Dict (MonadFix (WriterT w a)))
-> MonadFix a :- MonadFix (WriterT w a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadFix (WriterT w a))
MonadFix a => Dict (MonadFix (WriterT w a))
forall (a :: Constraint). a => Dict a
Dict
instance Monoid w => Lifting MonadPlus (Strict.WriterT w) where lifting :: forall (a :: * -> *). MonadPlus a :- MonadPlus (WriterT w a)
lifting = (MonadPlus a => Dict (MonadPlus (WriterT w a)))
-> MonadPlus a :- MonadPlus (WriterT w a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadPlus (WriterT w a))
MonadPlus a => Dict (MonadPlus (WriterT w a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Foldable (Strict.WriterT w) where lifting :: forall (a :: * -> *). Foldable a :- Foldable (WriterT w a)
lifting = (Foldable a => Dict (Foldable (WriterT w a)))
-> Foldable a :- Foldable (WriterT w a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Foldable (WriterT w a))
Foldable a => Dict (Foldable (WriterT w a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Traversable (Strict.WriterT w) where lifting :: forall (a :: * -> *). Traversable a :- Traversable (WriterT w a)
lifting = (Traversable a => Dict (Traversable (WriterT w a)))
-> Traversable a :- Traversable (WriterT w a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Traversable (WriterT w a))
Traversable a => Dict (Traversable (WriterT w a))
forall (a :: Constraint). a => Dict a
Dict
instance Monoid w => Lifting MonadIO (Strict.WriterT w) where lifting :: forall (a :: * -> *). MonadIO a :- MonadIO (WriterT w a)
lifting = (MonadIO a => Dict (MonadIO (WriterT w a)))
-> MonadIO a :- MonadIO (WriterT w a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadIO (WriterT w a))
MonadIO a => Dict (MonadIO (WriterT w a))
forall (a :: Constraint). a => Dict a
Dict
instance Show w => Lifting Show1 (Strict.WriterT w) where lifting :: forall (a :: * -> *). Show1 a :- Show1 (WriterT w a)
lifting = (Show1 a => Dict (Show1 (WriterT w a)))
-> Show1 a :- Show1 (WriterT w a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Show1 (WriterT w a))
Show1 a => Dict (Show1 (WriterT w a))
forall (a :: Constraint). a => Dict a
Dict
instance Eq w => Lifting Eq1 (Strict.WriterT w) where lifting :: forall (a :: * -> *). Eq1 a :- Eq1 (WriterT w a)
lifting = (Eq1 a => Dict (Eq1 (WriterT w a))) -> Eq1 a :- Eq1 (WriterT w a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Eq1 (WriterT w a))
Eq1 a => Dict (Eq1 (WriterT w a))
forall (a :: Constraint). a => Dict a
Dict
instance Ord w => Lifting Ord1 (Strict.WriterT w) where lifting :: forall (a :: * -> *). Ord1 a :- Ord1 (WriterT w a)
lifting = (Ord1 a => Dict (Ord1 (WriterT w a)))
-> Ord1 a :- Ord1 (WriterT w a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Ord1 (WriterT w a))
Ord1 a => Dict (Ord1 (WriterT w a))
forall (a :: Constraint). a => Dict a
Dict
instance Read w => Lifting Read1 (Strict.WriterT w) where lifting :: forall (a :: * -> *). Read1 a :- Read1 (WriterT w a)
lifting = (Read1 a => Dict (Read1 (WriterT w a)))
-> Read1 a :- Read1 (WriterT w a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Read1 (WriterT w a))
Read1 a => Dict (Read1 (WriterT w a))
forall (a :: Constraint). a => Dict a
Dict
instance (Show w, Show1 m) => Lifting Show (Strict.WriterT w m) where lifting :: forall a. Show a :- Show (WriterT w m a)
lifting = (Show a => Dict (Show (WriterT w m a)))
-> Show a :- Show (WriterT w m a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Show (WriterT w m a))
Show a => Dict (Show (WriterT w m a))
forall (a :: Constraint). a => Dict a
Dict
instance (Eq w, Eq1 m) => Lifting Eq (Strict.WriterT w m) where lifting :: forall a. Eq a :- Eq (WriterT w m a)
lifting = (Eq a => Dict (Eq (WriterT w m a))) -> Eq a :- Eq (WriterT w m a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Eq (WriterT w m a))
Eq a => Dict (Eq (WriterT w m a))
forall (a :: Constraint). a => Dict a
Dict
instance (Ord w, Ord1 m) => Lifting Ord (Strict.WriterT w m) where lifting :: forall a. Ord a :- Ord (WriterT w m a)
lifting = (Ord a => Dict (Ord (WriterT w m a)))
-> Ord a :- Ord (WriterT w m a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Ord (WriterT w m a))
Ord a => Dict (Ord (WriterT w m a))
forall (a :: Constraint). a => Dict a
Dict
instance (Read w, Read1 m) => Lifting Read (Strict.WriterT w m) where lifting :: forall a. Read a :- Read (WriterT w m a)
lifting = (Read a => Dict (Read (WriterT w m a)))
-> Read a :- Read (WriterT w m a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Read (WriterT w m a))
Read a => Dict (Read (WriterT w m a))
forall (a :: Constraint). a => Dict a
Dict

instance Lifting Functor (Lazy.WriterT w) where lifting :: forall (a :: * -> *). Functor a :- Functor (WriterT w a)
lifting = (Functor a => Dict (Functor (WriterT w a)))
-> Functor a :- Functor (WriterT w a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Functor (WriterT w a))
Functor a => Dict (Functor (WriterT w a))
forall (a :: Constraint). a => Dict a
Dict
instance Monoid w => Lifting Applicative (Lazy.WriterT w) where lifting :: forall (a :: * -> *). Applicative a :- Applicative (WriterT w a)
lifting = (Applicative a => Dict (Applicative (WriterT w a)))
-> Applicative a :- Applicative (WriterT w a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Applicative (WriterT w a))
Applicative a => Dict (Applicative (WriterT w a))
forall (a :: Constraint). a => Dict a
Dict
instance Monoid w => Lifting Alternative (Lazy.WriterT w) where lifting :: forall (a :: * -> *). Alternative a :- Alternative (WriterT w a)
lifting = (Alternative a => Dict (Alternative (WriterT w a)))
-> Alternative a :- Alternative (WriterT w a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Alternative (WriterT w a))
Alternative a => Dict (Alternative (WriterT w a))
forall (a :: Constraint). a => Dict a
Dict
instance Monoid w => Lifting Monad (Lazy.WriterT w) where lifting :: forall (a :: * -> *). Monad a :- Monad (WriterT w a)
lifting = (Monad a => Dict (Monad (WriterT w a)))
-> Monad a :- Monad (WriterT w a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Monad (WriterT w a))
Monad a => Dict (Monad (WriterT w a))
forall (a :: Constraint). a => Dict a
Dict
instance Monoid w => Lifting MonadFix (Lazy.WriterT w) where lifting :: forall (a :: * -> *). MonadFix a :- MonadFix (WriterT w a)
lifting = (MonadFix a => Dict (MonadFix (WriterT w a)))
-> MonadFix a :- MonadFix (WriterT w a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadFix (WriterT w a))
MonadFix a => Dict (MonadFix (WriterT w a))
forall (a :: Constraint). a => Dict a
Dict
instance Monoid w => Lifting MonadPlus (Lazy.WriterT w) where lifting :: forall (a :: * -> *). MonadPlus a :- MonadPlus (WriterT w a)
lifting = (MonadPlus a => Dict (MonadPlus (WriterT w a)))
-> MonadPlus a :- MonadPlus (WriterT w a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadPlus (WriterT w a))
MonadPlus a => Dict (MonadPlus (WriterT w a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Foldable (Lazy.WriterT w) where lifting :: forall (a :: * -> *). Foldable a :- Foldable (WriterT w a)
lifting = (Foldable a => Dict (Foldable (WriterT w a)))
-> Foldable a :- Foldable (WriterT w a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Foldable (WriterT w a))
Foldable a => Dict (Foldable (WriterT w a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Traversable (Lazy.WriterT w) where lifting :: forall (a :: * -> *). Traversable a :- Traversable (WriterT w a)
lifting = (Traversable a => Dict (Traversable (WriterT w a)))
-> Traversable a :- Traversable (WriterT w a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Traversable (WriterT w a))
Traversable a => Dict (Traversable (WriterT w a))
forall (a :: Constraint). a => Dict a
Dict
instance Monoid w => Lifting MonadIO (Lazy.WriterT w) where lifting :: forall (a :: * -> *). MonadIO a :- MonadIO (WriterT w a)
lifting = (MonadIO a => Dict (MonadIO (WriterT w a)))
-> MonadIO a :- MonadIO (WriterT w a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadIO (WriterT w a))
MonadIO a => Dict (MonadIO (WriterT w a))
forall (a :: Constraint). a => Dict a
Dict
instance Show w => Lifting Show1 (Lazy.WriterT w) where lifting :: forall (a :: * -> *). Show1 a :- Show1 (WriterT w a)
lifting = (Show1 a => Dict (Show1 (WriterT w a)))
-> Show1 a :- Show1 (WriterT w a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Show1 (WriterT w a))
Show1 a => Dict (Show1 (WriterT w a))
forall (a :: Constraint). a => Dict a
Dict
instance Eq w => Lifting Eq1 (Lazy.WriterT w) where lifting :: forall (a :: * -> *). Eq1 a :- Eq1 (WriterT w a)
lifting = (Eq1 a => Dict (Eq1 (WriterT w a))) -> Eq1 a :- Eq1 (WriterT w a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Eq1 (WriterT w a))
Eq1 a => Dict (Eq1 (WriterT w a))
forall (a :: Constraint). a => Dict a
Dict
instance Ord w => Lifting Ord1 (Lazy.WriterT w) where lifting :: forall (a :: * -> *). Ord1 a :- Ord1 (WriterT w a)
lifting = (Ord1 a => Dict (Ord1 (WriterT w a)))
-> Ord1 a :- Ord1 (WriterT w a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Ord1 (WriterT w a))
Ord1 a => Dict (Ord1 (WriterT w a))
forall (a :: Constraint). a => Dict a
Dict
instance Read w => Lifting Read1 (Lazy.WriterT w) where lifting :: forall (a :: * -> *). Read1 a :- Read1 (WriterT w a)
lifting = (Read1 a => Dict (Read1 (WriterT w a)))
-> Read1 a :- Read1 (WriterT w a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Read1 (WriterT w a))
Read1 a => Dict (Read1 (WriterT w a))
forall (a :: Constraint). a => Dict a
Dict
instance (Show w, Show1 m) => Lifting Show (Lazy.WriterT w m) where lifting :: forall a. Show a :- Show (WriterT w m a)
lifting = (Show a => Dict (Show (WriterT w m a)))
-> Show a :- Show (WriterT w m a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Show (WriterT w m a))
Show a => Dict (Show (WriterT w m a))
forall (a :: Constraint). a => Dict a
Dict
instance (Eq w, Eq1 m) => Lifting Eq (Lazy.WriterT w m) where lifting :: forall a. Eq a :- Eq (WriterT w m a)
lifting = (Eq a => Dict (Eq (WriterT w m a))) -> Eq a :- Eq (WriterT w m a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Eq (WriterT w m a))
Eq a => Dict (Eq (WriterT w m a))
forall (a :: Constraint). a => Dict a
Dict
instance (Ord w, Ord1 m) => Lifting Ord (Lazy.WriterT w m) where lifting :: forall a. Ord a :- Ord (WriterT w m a)
lifting = (Ord a => Dict (Ord (WriterT w m a)))
-> Ord a :- Ord (WriterT w m a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Ord (WriterT w m a))
Ord a => Dict (Ord (WriterT w m a))
forall (a :: Constraint). a => Dict a
Dict
instance (Read w, Read1 m) => Lifting Read (Lazy.WriterT w m) where lifting :: forall a. Read a :- Read (WriterT w m a)
lifting = (Read a => Dict (Read (WriterT w m a)))
-> Read a :- Read (WriterT w m a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Read (WriterT w m a))
Read a => Dict (Read (WriterT w m a))
forall (a :: Constraint). a => Dict a
Dict

instance Lifting Functor (ContT r) where lifting :: forall (a :: * -> *). Functor a :- Functor (ContT r a)
lifting = (Functor a => Dict (Functor (ContT r a)))
-> Functor a :- Functor (ContT r a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Functor (ContT r a))
Functor a => Dict (Functor (ContT r a))
forall (a :: Constraint). a => Dict a
Dict -- overconstrained
instance Lifting Applicative (ContT r) where lifting :: forall (a :: * -> *). Applicative a :- Applicative (ContT r a)
lifting = (Applicative a => Dict (Applicative (ContT r a)))
-> Applicative a :- Applicative (ContT r a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Applicative (ContT r a))
Applicative a => Dict (Applicative (ContT r a))
forall (a :: Constraint). a => Dict a
Dict -- overconstrained
instance Lifting Monad (ContT r) where lifting :: forall (a :: * -> *). Monad a :- Monad (ContT r a)
lifting = (Monad a => Dict (Monad (ContT r a)))
-> Monad a :- Monad (ContT r a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Monad (ContT r a))
Monad a => Dict (Monad (ContT r a))
forall (a :: Constraint). a => Dict a
Dict -- overconstrained
instance Lifting MonadIO (ContT r) where lifting :: forall (a :: * -> *). MonadIO a :- MonadIO (ContT r a)
lifting = (MonadIO a => Dict (MonadIO (ContT r a)))
-> MonadIO a :- MonadIO (ContT r a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadIO (ContT r a))
MonadIO a => Dict (MonadIO (ContT r a))
forall (a :: Constraint). a => Dict a
Dict

instance Lifting Functor IdentityT where lifting :: forall (a :: * -> *). Functor a :- Functor (IdentityT a)
lifting = (Functor a => Dict (Functor (IdentityT a)))
-> Functor a :- Functor (IdentityT a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Functor (IdentityT a))
Functor a => Dict (Functor (IdentityT a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Applicative IdentityT where lifting :: forall (a :: * -> *). Applicative a :- Applicative (IdentityT a)
lifting = (Applicative a => Dict (Applicative (IdentityT a)))
-> Applicative a :- Applicative (IdentityT a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Applicative (IdentityT a))
Applicative a => Dict (Applicative (IdentityT a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Alternative IdentityT where lifting :: forall (a :: * -> *). Alternative a :- Alternative (IdentityT a)
lifting = (Alternative a => Dict (Alternative (IdentityT a)))
-> Alternative a :- Alternative (IdentityT a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Alternative (IdentityT a))
Alternative a => Dict (Alternative (IdentityT a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Monad IdentityT where lifting :: forall (a :: * -> *). Monad a :- Monad (IdentityT a)
lifting = (Monad a => Dict (Monad (IdentityT a)))
-> Monad a :- Monad (IdentityT a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Monad (IdentityT a))
Monad a => Dict (Monad (IdentityT a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting MonadPlus IdentityT where lifting :: forall (a :: * -> *). MonadPlus a :- MonadPlus (IdentityT a)
lifting = (MonadPlus a => Dict (MonadPlus (IdentityT a)))
-> MonadPlus a :- MonadPlus (IdentityT a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadPlus (IdentityT a))
MonadPlus a => Dict (MonadPlus (IdentityT a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting MonadFix IdentityT where lifting :: forall (a :: * -> *). MonadFix a :- MonadFix (IdentityT a)
lifting = (MonadFix a => Dict (MonadFix (IdentityT a)))
-> MonadFix a :- MonadFix (IdentityT a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadFix (IdentityT a))
MonadFix a => Dict (MonadFix (IdentityT a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Foldable IdentityT where lifting :: forall (a :: * -> *). Foldable a :- Foldable (IdentityT a)
lifting = (Foldable a => Dict (Foldable (IdentityT a)))
-> Foldable a :- Foldable (IdentityT a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Foldable (IdentityT a))
Foldable a => Dict (Foldable (IdentityT a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Traversable IdentityT where lifting :: forall (a :: * -> *). Traversable a :- Traversable (IdentityT a)
lifting = (Traversable a => Dict (Traversable (IdentityT a)))
-> Traversable a :- Traversable (IdentityT a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Traversable (IdentityT a))
Traversable a => Dict (Traversable (IdentityT a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting MonadIO IdentityT where lifting :: forall (a :: * -> *). MonadIO a :- MonadIO (IdentityT a)
lifting = (MonadIO a => Dict (MonadIO (IdentityT a)))
-> MonadIO a :- MonadIO (IdentityT a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadIO (IdentityT a))
MonadIO a => Dict (MonadIO (IdentityT a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Show1 IdentityT where lifting :: forall (a :: * -> *). Show1 a :- Show1 (IdentityT a)
lifting = (Show1 a => Dict (Show1 (IdentityT a)))
-> Show1 a :- Show1 (IdentityT a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Show1 (IdentityT a))
Show1 a => Dict (Show1 (IdentityT a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Read1 IdentityT where lifting :: forall (a :: * -> *). Read1 a :- Read1 (IdentityT a)
lifting = (Read1 a => Dict (Read1 (IdentityT a)))
-> Read1 a :- Read1 (IdentityT a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Read1 (IdentityT a))
Read1 a => Dict (Read1 (IdentityT a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Ord1 IdentityT where lifting :: forall (a :: * -> *). Ord1 a :- Ord1 (IdentityT a)
lifting = (Ord1 a => Dict (Ord1 (IdentityT a)))
-> Ord1 a :- Ord1 (IdentityT a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Ord1 (IdentityT a))
Ord1 a => Dict (Ord1 (IdentityT a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Eq1 IdentityT where lifting :: forall (a :: * -> *). Eq1 a :- Eq1 (IdentityT a)
lifting = (Eq1 a => Dict (Eq1 (IdentityT a))) -> Eq1 a :- Eq1 (IdentityT a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Eq1 (IdentityT a))
Eq1 a => Dict (Eq1 (IdentityT a))
forall (a :: Constraint). a => Dict a
Dict
instance Show1 m => Lifting Show (IdentityT m) where lifting :: forall a. Show a :- Show (IdentityT m a)
lifting = (Show a => Dict (Show (IdentityT m a)))
-> Show a :- Show (IdentityT m a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Show (IdentityT m a))
Show a => Dict (Show (IdentityT m a))
forall (a :: Constraint). a => Dict a
Dict
instance Read1 m => Lifting Read (IdentityT m) where lifting :: forall a. Read a :- Read (IdentityT m a)
lifting = (Read a => Dict (Read (IdentityT m a)))
-> Read a :- Read (IdentityT m a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Read (IdentityT m a))
Read a => Dict (Read (IdentityT m a))
forall (a :: Constraint). a => Dict a
Dict
instance Ord1 m => Lifting Ord (IdentityT m) where lifting :: forall a. Ord a :- Ord (IdentityT m a)
lifting = (Ord a => Dict (Ord (IdentityT m a)))
-> Ord a :- Ord (IdentityT m a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Ord (IdentityT m a))
Ord a => Dict (Ord (IdentityT m a))
forall (a :: Constraint). a => Dict a
Dict
instance Eq1 m => Lifting Eq (IdentityT m) where lifting :: forall a. Eq a :- Eq (IdentityT m a)
lifting = (Eq a => Dict (Eq (IdentityT m a))) -> Eq a :- Eq (IdentityT m a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Eq (IdentityT m a))
Eq a => Dict (Eq (IdentityT m a))
forall (a :: Constraint). a => Dict a
Dict

instance Lifting Functor MaybeT where lifting :: forall (a :: * -> *). Functor a :- Functor (MaybeT a)
lifting = (Functor a => Dict (Functor (MaybeT a)))
-> Functor a :- Functor (MaybeT a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Functor (MaybeT a))
Functor a => Dict (Functor (MaybeT a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Monad MaybeT where lifting :: forall (a :: * -> *). Monad a :- Monad (MaybeT a)
lifting = (Monad a => Dict (Monad (MaybeT a))) -> Monad a :- Monad (MaybeT a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Monad (MaybeT a))
Monad a => Dict (Monad (MaybeT a))
forall (a :: Constraint). a => Dict a
Dict
-- instance Lifting MonadFix MaybeT where lifting = Sub Dict
instance Lifting MonadPlus MaybeT where lifting :: forall (a :: * -> *). MonadPlus a :- MonadPlus (MaybeT a)
lifting = (MonadPlus a => Dict (MonadPlus (MaybeT a)))
-> MonadPlus a :- MonadPlus (MaybeT a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadPlus (MaybeT a))
MonadPlus a => Dict (MonadPlus (MaybeT a))
forall (a :: Constraint). a => Dict a
Dict -- overconstrained
instance Lifting Foldable MaybeT where lifting :: forall (a :: * -> *). Foldable a :- Foldable (MaybeT a)
lifting = (Foldable a => Dict (Foldable (MaybeT a)))
-> Foldable a :- Foldable (MaybeT a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Foldable (MaybeT a))
Foldable a => Dict (Foldable (MaybeT a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Traversable MaybeT where lifting :: forall (a :: * -> *). Traversable a :- Traversable (MaybeT a)
lifting = (Traversable a => Dict (Traversable (MaybeT a)))
-> Traversable a :- Traversable (MaybeT a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Traversable (MaybeT a))
Traversable a => Dict (Traversable (MaybeT a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting MonadIO MaybeT where lifting :: forall (a :: * -> *). MonadIO a :- MonadIO (MaybeT a)
lifting = (MonadIO a => Dict (MonadIO (MaybeT a)))
-> MonadIO a :- MonadIO (MaybeT a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadIO (MaybeT a))
MonadIO a => Dict (MonadIO (MaybeT a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Show1 MaybeT where lifting :: forall (a :: * -> *). Show1 a :- Show1 (MaybeT a)
lifting = (Show1 a => Dict (Show1 (MaybeT a))) -> Show1 a :- Show1 (MaybeT a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Show1 (MaybeT a))
Show1 a => Dict (Show1 (MaybeT a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Read1 MaybeT where lifting :: forall (a :: * -> *). Read1 a :- Read1 (MaybeT a)
lifting = (Read1 a => Dict (Read1 (MaybeT a))) -> Read1 a :- Read1 (MaybeT a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Read1 (MaybeT a))
Read1 a => Dict (Read1 (MaybeT a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Ord1 MaybeT where lifting :: forall (a :: * -> *). Ord1 a :- Ord1 (MaybeT a)
lifting = (Ord1 a => Dict (Ord1 (MaybeT a))) -> Ord1 a :- Ord1 (MaybeT a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Ord1 (MaybeT a))
Ord1 a => Dict (Ord1 (MaybeT a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Eq1 MaybeT where lifting :: forall (a :: * -> *). Eq1 a :- Eq1 (MaybeT a)
lifting = (Eq1 a => Dict (Eq1 (MaybeT a))) -> Eq1 a :- Eq1 (MaybeT a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Eq1 (MaybeT a))
Eq1 a => Dict (Eq1 (MaybeT a))
forall (a :: Constraint). a => Dict a
Dict
instance Show1 m => Lifting Show (MaybeT m) where lifting :: forall a. Show a :- Show (MaybeT m a)
lifting = (Show a => Dict (Show (MaybeT m a))) -> Show a :- Show (MaybeT m a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Show (MaybeT m a))
Show a => Dict (Show (MaybeT m a))
forall (a :: Constraint). a => Dict a
Dict
instance Read1 m => Lifting Read (MaybeT m) where lifting :: forall a. Read a :- Read (MaybeT m a)
lifting = (Read a => Dict (Read (MaybeT m a))) -> Read a :- Read (MaybeT m a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Read (MaybeT m a))
Read a => Dict (Read (MaybeT m a))
forall (a :: Constraint). a => Dict a
Dict
instance Ord1 m => Lifting Ord (MaybeT m) where lifting :: forall a. Ord a :- Ord (MaybeT m a)
lifting = (Ord a => Dict (Ord (MaybeT m a))) -> Ord a :- Ord (MaybeT m a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Ord (MaybeT m a))
Ord a => Dict (Ord (MaybeT m a))
forall (a :: Constraint). a => Dict a
Dict
instance Eq1 m => Lifting Eq (MaybeT m) where lifting :: forall a. Eq a :- Eq (MaybeT m a)
lifting = (Eq a => Dict (Eq (MaybeT m a))) -> Eq a :- Eq (MaybeT m a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Eq (MaybeT m a))
Eq a => Dict (Eq (MaybeT m a))
forall (a :: Constraint). a => Dict a
Dict

instance Lifting Functor Reverse where lifting :: forall (a :: * -> *). Functor a :- Functor (Reverse a)
lifting = (Functor a => Dict (Functor (Reverse a)))
-> Functor a :- Functor (Reverse a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Functor (Reverse a))
Functor a => Dict (Functor (Reverse a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Applicative Reverse where lifting :: forall (a :: * -> *). Applicative a :- Applicative (Reverse a)
lifting = (Applicative a => Dict (Applicative (Reverse a)))
-> Applicative a :- Applicative (Reverse a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Applicative (Reverse a))
Applicative a => Dict (Applicative (Reverse a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Alternative Reverse where lifting :: forall (a :: * -> *). Alternative a :- Alternative (Reverse a)
lifting = (Alternative a => Dict (Alternative (Reverse a)))
-> Alternative a :- Alternative (Reverse a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Alternative (Reverse a))
Alternative a => Dict (Alternative (Reverse a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Foldable Reverse where lifting :: forall (a :: * -> *). Foldable a :- Foldable (Reverse a)
lifting = (Foldable a => Dict (Foldable (Reverse a)))
-> Foldable a :- Foldable (Reverse a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Foldable (Reverse a))
Foldable a => Dict (Foldable (Reverse a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Traversable Reverse where lifting :: forall (a :: * -> *). Traversable a :- Traversable (Reverse a)
lifting = (Traversable a => Dict (Traversable (Reverse a)))
-> Traversable a :- Traversable (Reverse a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Traversable (Reverse a))
Traversable a => Dict (Traversable (Reverse a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Show1 Reverse where lifting :: forall (a :: * -> *). Show1 a :- Show1 (Reverse a)
lifting = (Show1 a => Dict (Show1 (Reverse a)))
-> Show1 a :- Show1 (Reverse a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Show1 (Reverse a))
Show1 a => Dict (Show1 (Reverse a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Read1 Reverse where lifting :: forall (a :: * -> *). Read1 a :- Read1 (Reverse a)
lifting = (Read1 a => Dict (Read1 (Reverse a)))
-> Read1 a :- Read1 (Reverse a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Read1 (Reverse a))
Read1 a => Dict (Read1 (Reverse a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Ord1 Reverse where lifting :: forall (a :: * -> *). Ord1 a :- Ord1 (Reverse a)
lifting = (Ord1 a => Dict (Ord1 (Reverse a))) -> Ord1 a :- Ord1 (Reverse a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Ord1 (Reverse a))
Ord1 a => Dict (Ord1 (Reverse a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Eq1 Reverse where lifting :: forall (a :: * -> *). Eq1 a :- Eq1 (Reverse a)
lifting = (Eq1 a => Dict (Eq1 (Reverse a))) -> Eq1 a :- Eq1 (Reverse a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Eq1 (Reverse a))
Eq1 a => Dict (Eq1 (Reverse a))
forall (a :: Constraint). a => Dict a
Dict
instance Show1 f => Lifting Show (Reverse f) where lifting :: forall a. Show a :- Show (Reverse f a)
lifting = (Show a => Dict (Show (Reverse f a)))
-> Show a :- Show (Reverse f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Show (Reverse f a))
Show a => Dict (Show (Reverse f a))
forall (a :: Constraint). a => Dict a
Dict
instance Read1 f => Lifting Read (Reverse f) where lifting :: forall a. Read a :- Read (Reverse f a)
lifting = (Read a => Dict (Read (Reverse f a)))
-> Read a :- Read (Reverse f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Read (Reverse f a))
Read a => Dict (Read (Reverse f a))
forall (a :: Constraint). a => Dict a
Dict
instance Ord1 f => Lifting Ord (Reverse f) where lifting :: forall a. Ord a :- Ord (Reverse f a)
lifting = (Ord a => Dict (Ord (Reverse f a))) -> Ord a :- Ord (Reverse f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Ord (Reverse f a))
Ord a => Dict (Ord (Reverse f a))
forall (a :: Constraint). a => Dict a
Dict
instance Eq1 f => Lifting Eq (Reverse f) where lifting :: forall a. Eq a :- Eq (Reverse f a)
lifting = (Eq a => Dict (Eq (Reverse f a))) -> Eq a :- Eq (Reverse f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Eq (Reverse f a))
Eq a => Dict (Eq (Reverse f a))
forall (a :: Constraint). a => Dict a
Dict

instance Lifting Functor Backwards where lifting :: forall (a :: * -> *). Functor a :- Functor (Backwards a)
lifting = (Functor a => Dict (Functor (Backwards a)))
-> Functor a :- Functor (Backwards a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Functor (Backwards a))
Functor a => Dict (Functor (Backwards a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Foldable Backwards where lifting :: forall (a :: * -> *). Foldable a :- Foldable (Backwards a)
lifting = (Foldable a => Dict (Foldable (Backwards a)))
-> Foldable a :- Foldable (Backwards a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Foldable (Backwards a))
Foldable a => Dict (Foldable (Backwards a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Traversable Backwards where lifting :: forall (a :: * -> *). Traversable a :- Traversable (Backwards a)
lifting = (Traversable a => Dict (Traversable (Backwards a)))
-> Traversable a :- Traversable (Backwards a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Traversable (Backwards a))
Traversable a => Dict (Traversable (Backwards a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Applicative Backwards where lifting :: forall (a :: * -> *). Applicative a :- Applicative (Backwards a)
lifting = (Applicative a => Dict (Applicative (Backwards a)))
-> Applicative a :- Applicative (Backwards a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Applicative (Backwards a))
Applicative a => Dict (Applicative (Backwards a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Alternative Backwards where lifting :: forall (a :: * -> *). Alternative a :- Alternative (Backwards a)
lifting = (Alternative a => Dict (Alternative (Backwards a)))
-> Alternative a :- Alternative (Backwards a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Alternative (Backwards a))
Alternative a => Dict (Alternative (Backwards a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Show1 Backwards where lifting :: forall (a :: * -> *). Show1 a :- Show1 (Backwards a)
lifting = (Show1 a => Dict (Show1 (Backwards a)))
-> Show1 a :- Show1 (Backwards a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Show1 (Backwards a))
Show1 a => Dict (Show1 (Backwards a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Read1 Backwards where lifting :: forall (a :: * -> *). Read1 a :- Read1 (Backwards a)
lifting = (Read1 a => Dict (Read1 (Backwards a)))
-> Read1 a :- Read1 (Backwards a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Read1 (Backwards a))
Read1 a => Dict (Read1 (Backwards a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Ord1 Backwards where lifting :: forall (a :: * -> *). Ord1 a :- Ord1 (Backwards a)
lifting = (Ord1 a => Dict (Ord1 (Backwards a)))
-> Ord1 a :- Ord1 (Backwards a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Ord1 (Backwards a))
Ord1 a => Dict (Ord1 (Backwards a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Eq1 Backwards where lifting :: forall (a :: * -> *). Eq1 a :- Eq1 (Backwards a)
lifting = (Eq1 a => Dict (Eq1 (Backwards a))) -> Eq1 a :- Eq1 (Backwards a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Eq1 (Backwards a))
Eq1 a => Dict (Eq1 (Backwards a))
forall (a :: Constraint). a => Dict a
Dict
instance Show1 f => Lifting Show (Backwards f) where lifting :: forall a. Show a :- Show (Backwards f a)
lifting = (Show a => Dict (Show (Backwards f a)))
-> Show a :- Show (Backwards f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Show (Backwards f a))
Show a => Dict (Show (Backwards f a))
forall (a :: Constraint). a => Dict a
Dict
instance Read1 f => Lifting Read (Backwards f) where lifting :: forall a. Read a :- Read (Backwards f a)
lifting = (Read a => Dict (Read (Backwards f a)))
-> Read a :- Read (Backwards f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Read (Backwards f a))
Read a => Dict (Read (Backwards f a))
forall (a :: Constraint). a => Dict a
Dict
instance Ord1 f => Lifting Ord (Backwards f) where lifting :: forall a. Ord a :- Ord (Backwards f a)
lifting = (Ord a => Dict (Ord (Backwards f a)))
-> Ord a :- Ord (Backwards f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Ord (Backwards f a))
Ord a => Dict (Ord (Backwards f a))
forall (a :: Constraint). a => Dict a
Dict
instance Eq1 f => Lifting Eq (Backwards f) where lifting :: forall a. Eq a :- Eq (Backwards f a)
lifting = (Eq a => Dict (Eq (Backwards f a))) -> Eq a :- Eq (Backwards f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Eq (Backwards f a))
Eq a => Dict (Eq (Backwards f a))
forall (a :: Constraint). a => Dict a
Dict

instance Lifting Functor Lift where lifting :: forall (a :: * -> *). Functor a :- Functor (Lift a)
lifting = (Functor a => Dict (Functor (Lift a)))
-> Functor a :- Functor (Lift a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Functor (Lift a))
Functor a => Dict (Functor (Lift a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Foldable Lift where lifting :: forall (a :: * -> *). Foldable a :- Foldable (Lift a)
lifting = (Foldable a => Dict (Foldable (Lift a)))
-> Foldable a :- Foldable (Lift a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Foldable (Lift a))
Foldable a => Dict (Foldable (Lift a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Traversable Lift where lifting :: forall (a :: * -> *). Traversable a :- Traversable (Lift a)
lifting = (Traversable a => Dict (Traversable (Lift a)))
-> Traversable a :- Traversable (Lift a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Traversable (Lift a))
Traversable a => Dict (Traversable (Lift a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Applicative Lift where lifting :: forall (a :: * -> *). Applicative a :- Applicative (Lift a)
lifting = (Applicative a => Dict (Applicative (Lift a)))
-> Applicative a :- Applicative (Lift a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Applicative (Lift a))
Applicative a => Dict (Applicative (Lift a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Alternative Lift where lifting :: forall (a :: * -> *). Alternative a :- Alternative (Lift a)
lifting = (Alternative a => Dict (Alternative (Lift a)))
-> Alternative a :- Alternative (Lift a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Alternative (Lift a))
Alternative a => Dict (Alternative (Lift a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Show1 Lift where lifting :: forall (a :: * -> *). Show1 a :- Show1 (Lift a)
lifting = (Show1 a => Dict (Show1 (Lift a))) -> Show1 a :- Show1 (Lift a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Show1 (Lift a))
Show1 a => Dict (Show1 (Lift a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Read1 Lift where lifting :: forall (a :: * -> *). Read1 a :- Read1 (Lift a)
lifting = (Read1 a => Dict (Read1 (Lift a))) -> Read1 a :- Read1 (Lift a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Read1 (Lift a))
Read1 a => Dict (Read1 (Lift a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Ord1 Lift where lifting :: forall (a :: * -> *). Ord1 a :- Ord1 (Lift a)
lifting = (Ord1 a => Dict (Ord1 (Lift a))) -> Ord1 a :- Ord1 (Lift a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Ord1 (Lift a))
Ord1 a => Dict (Ord1 (Lift a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Eq1 Lift where lifting :: forall (a :: * -> *). Eq1 a :- Eq1 (Lift a)
lifting = (Eq1 a => Dict (Eq1 (Lift a))) -> Eq1 a :- Eq1 (Lift a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Eq1 (Lift a))
Eq1 a => Dict (Eq1 (Lift a))
forall (a :: Constraint). a => Dict a
Dict
instance Show1 f => Lifting Show (Lift f) where lifting :: forall a. Show a :- Show (Lift f a)
lifting = (Show a => Dict (Show (Lift f a))) -> Show a :- Show (Lift f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Show (Lift f a))
Show a => Dict (Show (Lift f a))
forall (a :: Constraint). a => Dict a
Dict
instance Read1 f => Lifting Read (Lift f) where lifting :: forall a. Read a :- Read (Lift f a)
lifting = (Read a => Dict (Read (Lift f a))) -> Read a :- Read (Lift f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Read (Lift f a))
Read a => Dict (Read (Lift f a))
forall (a :: Constraint). a => Dict a
Dict
instance Ord1 f => Lifting Ord (Lift f) where lifting :: forall a. Ord a :- Ord (Lift f a)
lifting = (Ord a => Dict (Ord (Lift f a))) -> Ord a :- Ord (Lift f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Ord (Lift f a))
Ord a => Dict (Ord (Lift f a))
forall (a :: Constraint). a => Dict a
Dict
instance Eq1 f => Lifting Eq (Lift f) where lifting :: forall a. Eq a :- Eq (Lift f a)
lifting = (Eq a => Dict (Eq (Lift f a))) -> Eq a :- Eq (Lift f a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Eq (Lift f a))
Eq a => Dict (Eq (Lift f a))
forall (a :: Constraint). a => Dict a
Dict

instance Lifting Eq Identity where lifting :: forall a. Eq a :- Eq (Identity a)
lifting = (Eq a => Dict (Eq (Identity a))) -> Eq a :- Eq (Identity a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Eq (Identity a))
Eq a => Dict (Eq (Identity a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Ord Identity where lifting :: forall a. Ord a :- Ord (Identity a)
lifting = (Ord a => Dict (Ord (Identity a))) -> Ord a :- Ord (Identity a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Ord (Identity a))
Ord a => Dict (Ord (Identity a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Show Identity where lifting :: forall a. Show a :- Show (Identity a)
lifting = (Show a => Dict (Show (Identity a))) -> Show a :- Show (Identity a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Show (Identity a))
Show a => Dict (Show (Identity a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting Read Identity where lifting :: forall a. Read a :- Read (Identity a)
lifting = (Read a => Dict (Read (Identity a))) -> Read a :- Read (Identity a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Read (Identity a))
Read a => Dict (Read (Identity a))
forall (a :: Constraint). a => Dict a
Dict

instance Lifting MonadCont MaybeT where lifting :: forall (a :: * -> *). MonadCont a :- MonadCont (MaybeT a)
lifting = (MonadCont a => Dict (MonadCont (MaybeT a)))
-> MonadCont a :- MonadCont (MaybeT a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadCont (MaybeT a))
MonadCont a => Dict (MonadCont (MaybeT a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting MonadCont IdentityT where lifting :: forall (a :: * -> *). MonadCont a :- MonadCont (IdentityT a)
lifting = (MonadCont a => Dict (MonadCont (IdentityT a)))
-> MonadCont a :- MonadCont (IdentityT a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadCont (IdentityT a))
MonadCont a => Dict (MonadCont (IdentityT a))
forall (a :: Constraint). a => Dict a
Dict
instance Monoid w => Lifting MonadCont (Strict.WriterT w) where lifting :: forall (a :: * -> *). MonadCont a :- MonadCont (WriterT w a)
lifting = (MonadCont a => Dict (MonadCont (WriterT w a)))
-> MonadCont a :- MonadCont (WriterT w a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadCont (WriterT w a))
MonadCont a => Dict (MonadCont (WriterT w a))
forall (a :: Constraint). a => Dict a
Dict
instance Monoid w => Lifting MonadCont (Lazy.WriterT w) where lifting :: forall (a :: * -> *). MonadCont a :- MonadCont (WriterT w a)
lifting = (MonadCont a => Dict (MonadCont (WriterT w a)))
-> MonadCont a :- MonadCont (WriterT w a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadCont (WriterT w a))
MonadCont a => Dict (MonadCont (WriterT w a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting MonadCont (ExceptT w) where lifting :: forall (a :: * -> *). MonadCont a :- MonadCont (ExceptT w a)
lifting = (MonadCont a => Dict (MonadCont (ExceptT w a)))
-> MonadCont a :- MonadCont (ExceptT w a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadCont (ExceptT w a))
MonadCont a => Dict (MonadCont (ExceptT w a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting MonadCont (Strict.StateT s) where lifting :: forall (a :: * -> *). MonadCont a :- MonadCont (StateT s a)
lifting = (MonadCont a => Dict (MonadCont (StateT s a)))
-> MonadCont a :- MonadCont (StateT s a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadCont (StateT s a))
MonadCont a => Dict (MonadCont (StateT s a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting MonadCont (Lazy.StateT s) where lifting :: forall (a :: * -> *). MonadCont a :- MonadCont (StateT s a)
lifting = (MonadCont a => Dict (MonadCont (StateT s a)))
-> MonadCont a :- MonadCont (StateT s a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadCont (StateT s a))
MonadCont a => Dict (MonadCont (StateT s a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting MonadCont (ReaderT e) where lifting :: forall (a :: * -> *). MonadCont a :- MonadCont (ReaderT e a)
lifting = (MonadCont a => Dict (MonadCont (ReaderT e a)))
-> MonadCont a :- MonadCont (ReaderT e a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadCont (ReaderT e a))
MonadCont a => Dict (MonadCont (ReaderT e a))
forall (a :: Constraint). a => Dict a
Dict
instance Monoid w => Lifting MonadCont (Strict.RWST r w s) where lifting :: forall (a :: * -> *). MonadCont a :- MonadCont (RWST r w s a)
lifting = (MonadCont a => Dict (MonadCont (RWST r w s a)))
-> MonadCont a :- MonadCont (RWST r w s a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadCont (RWST r w s a))
MonadCont a => Dict (MonadCont (RWST r w s a))
forall (a :: Constraint). a => Dict a
Dict
instance Monoid w => Lifting MonadCont (Lazy.RWST r w s) where lifting :: forall (a :: * -> *). MonadCont a :- MonadCont (RWST r w s a)
lifting = (MonadCont a => Dict (MonadCont (RWST r w s a)))
-> MonadCont a :- MonadCont (RWST r w s a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadCont (RWST r w s a))
MonadCont a => Dict (MonadCont (RWST r w s a))
forall (a :: Constraint). a => Dict a
Dict

instance Lifting (MonadError e) MaybeT where lifting :: forall (a :: * -> *). MonadError e a :- MonadError e (MaybeT a)
lifting = (MonadError e a => Dict (MonadError e (MaybeT a)))
-> MonadError e a :- MonadError e (MaybeT a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadError e (MaybeT a))
MonadError e a => Dict (MonadError e (MaybeT a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting (MonadError e) IdentityT where lifting :: forall (a :: * -> *). MonadError e a :- MonadError e (IdentityT a)
lifting = (MonadError e a => Dict (MonadError e (IdentityT a)))
-> MonadError e a :- MonadError e (IdentityT a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadError e (IdentityT a))
MonadError e a => Dict (MonadError e (IdentityT a))
forall (a :: Constraint). a => Dict a
Dict
instance Monoid w => Lifting (MonadError e) (Strict.WriterT w) where lifting :: forall (a :: * -> *). MonadError e a :- MonadError e (WriterT w a)
lifting = (MonadError e a => Dict (MonadError e (WriterT w a)))
-> MonadError e a :- MonadError e (WriterT w a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadError e (WriterT w a))
MonadError e a => Dict (MonadError e (WriterT w a))
forall (a :: Constraint). a => Dict a
Dict
instance Monoid w => Lifting (MonadError e) (Lazy.WriterT w) where lifting :: forall (a :: * -> *). MonadError e a :- MonadError e (WriterT w a)
lifting = (MonadError e a => Dict (MonadError e (WriterT w a)))
-> MonadError e a :- MonadError e (WriterT w a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadError e (WriterT w a))
MonadError e a => Dict (MonadError e (WriterT w a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting (MonadError e) (Strict.StateT s) where lifting :: forall (a :: * -> *). MonadError e a :- MonadError e (StateT s a)
lifting = (MonadError e a => Dict (MonadError e (StateT s a)))
-> MonadError e a :- MonadError e (StateT s a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadError e (StateT s a))
MonadError e a => Dict (MonadError e (StateT s a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting (MonadError e) (Lazy.StateT s) where lifting :: forall (a :: * -> *). MonadError e a :- MonadError e (StateT s a)
lifting = (MonadError e a => Dict (MonadError e (StateT s a)))
-> MonadError e a :- MonadError e (StateT s a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadError e (StateT s a))
MonadError e a => Dict (MonadError e (StateT s a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting (MonadError e) (ReaderT r) where lifting :: forall (a :: * -> *). MonadError e a :- MonadError e (ReaderT r a)
lifting = (MonadError e a => Dict (MonadError e (ReaderT r a)))
-> MonadError e a :- MonadError e (ReaderT r a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadError e (ReaderT r a))
MonadError e a => Dict (MonadError e (ReaderT r a))
forall (a :: Constraint). a => Dict a
Dict
instance Monoid w => Lifting (MonadError e) (Strict.RWST r w s) where lifting :: forall (a :: * -> *). MonadError e a :- MonadError e (RWST r w s a)
lifting = (MonadError e a => Dict (MonadError e (RWST r w s a)))
-> MonadError e a :- MonadError e (RWST r w s a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadError e (RWST r w s a))
MonadError e a => Dict (MonadError e (RWST r w s a))
forall (a :: Constraint). a => Dict a
Dict
instance Monoid w => Lifting (MonadError e) (Lazy.RWST r w s) where lifting :: forall (a :: * -> *). MonadError e a :- MonadError e (RWST r w s a)
lifting = (MonadError e a => Dict (MonadError e (RWST r w s a)))
-> MonadError e a :- MonadError e (RWST r w s a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadError e (RWST r w s a))
MonadError e a => Dict (MonadError e (RWST r w s a))
forall (a :: Constraint). a => Dict a
Dict

instance Lifting (MonadRWS r w s) MaybeT where lifting :: forall (a :: * -> *). MonadRWS r w s a :- MonadRWS r w s (MaybeT a)
lifting = (MonadRWS r w s a => Dict (MonadRWS r w s (MaybeT a)))
-> MonadRWS r w s a :- MonadRWS r w s (MaybeT a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadRWS r w s (MaybeT a))
MonadRWS r w s a => Dict (MonadRWS r w s (MaybeT a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting (MonadRWS r w s) IdentityT where lifting :: forall (a :: * -> *).
MonadRWS r w s a :- MonadRWS r w s (IdentityT a)
lifting = (MonadRWS r w s a => Dict (MonadRWS r w s (IdentityT a)))
-> MonadRWS r w s a :- MonadRWS r w s (IdentityT a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadRWS r w s (IdentityT a))
MonadRWS r w s a => Dict (MonadRWS r w s (IdentityT a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting (MonadRWS r w s) (ExceptT e) where lifting :: forall (a :: * -> *).
MonadRWS r w s a :- MonadRWS r w s (ExceptT e a)
lifting = (MonadRWS r w s a => Dict (MonadRWS r w s (ExceptT e a)))
-> MonadRWS r w s a :- MonadRWS r w s (ExceptT e a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadRWS r w s (ExceptT e a))
MonadRWS r w s a => Dict (MonadRWS r w s (ExceptT e a))
forall (a :: Constraint). a => Dict a
Dict

instance Lifting (MonadReader r) MaybeT where lifting :: forall (a :: * -> *). MonadReader r a :- MonadReader r (MaybeT a)
lifting = (MonadReader r a => Dict (MonadReader r (MaybeT a)))
-> MonadReader r a :- MonadReader r (MaybeT a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadReader r (MaybeT a))
MonadReader r a => Dict (MonadReader r (MaybeT a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting (MonadReader r) IdentityT where lifting :: forall (a :: * -> *).
MonadReader r a :- MonadReader r (IdentityT a)
lifting = (MonadReader r a => Dict (MonadReader r (IdentityT a)))
-> MonadReader r a :- MonadReader r (IdentityT a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadReader r (IdentityT a))
MonadReader r a => Dict (MonadReader r (IdentityT a))
forall (a :: Constraint). a => Dict a
Dict
instance Monoid w => Lifting (MonadReader r) (Strict.WriterT w) where lifting :: forall (a :: * -> *).
MonadReader r a :- MonadReader r (WriterT w a)
lifting = (MonadReader r a => Dict (MonadReader r (WriterT w a)))
-> MonadReader r a :- MonadReader r (WriterT w a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadReader r (WriterT w a))
MonadReader r a => Dict (MonadReader r (WriterT w a))
forall (a :: Constraint). a => Dict a
Dict
instance Monoid w => Lifting (MonadReader r) (Lazy.WriterT w) where lifting :: forall (a :: * -> *).
MonadReader r a :- MonadReader r (WriterT w a)
lifting = (MonadReader r a => Dict (MonadReader r (WriterT w a)))
-> MonadReader r a :- MonadReader r (WriterT w a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadReader r (WriterT w a))
MonadReader r a => Dict (MonadReader r (WriterT w a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting (MonadReader r) (Strict.StateT s) where lifting :: forall (a :: * -> *). MonadReader r a :- MonadReader r (StateT s a)
lifting = (MonadReader r a => Dict (MonadReader r (StateT s a)))
-> MonadReader r a :- MonadReader r (StateT s a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadReader r (StateT s a))
MonadReader r a => Dict (MonadReader r (StateT s a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting (MonadReader r) (Lazy.StateT s) where lifting :: forall (a :: * -> *). MonadReader r a :- MonadReader r (StateT s a)
lifting = (MonadReader r a => Dict (MonadReader r (StateT s a)))
-> MonadReader r a :- MonadReader r (StateT s a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadReader r (StateT s a))
MonadReader r a => Dict (MonadReader r (StateT s a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting (MonadReader r) (ExceptT e) where lifting :: forall (a :: * -> *).
MonadReader r a :- MonadReader r (ExceptT e a)
lifting = (MonadReader r a => Dict (MonadReader r (ExceptT e a)))
-> MonadReader r a :- MonadReader r (ExceptT e a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadReader r (ExceptT e a))
MonadReader r a => Dict (MonadReader r (ExceptT e a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting (MonadReader r) (ContT r') where lifting :: forall (a :: * -> *). MonadReader r a :- MonadReader r (ContT r' a)
lifting = (MonadReader r a => Dict (MonadReader r (ContT r' a)))
-> MonadReader r a :- MonadReader r (ContT r' a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadReader r (ContT r' a))
MonadReader r a => Dict (MonadReader r (ContT r' a))
forall (a :: Constraint). a => Dict a
Dict

instance Lifting (MonadState s) MaybeT where lifting :: forall (a :: * -> *). MonadState s a :- MonadState s (MaybeT a)
lifting = (MonadState s a => Dict (MonadState s (MaybeT a)))
-> MonadState s a :- MonadState s (MaybeT a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadState s (MaybeT a))
MonadState s a => Dict (MonadState s (MaybeT a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting (MonadState s) IdentityT where lifting :: forall (a :: * -> *). MonadState s a :- MonadState s (IdentityT a)
lifting = (MonadState s a => Dict (MonadState s (IdentityT a)))
-> MonadState s a :- MonadState s (IdentityT a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadState s (IdentityT a))
MonadState s a => Dict (MonadState s (IdentityT a))
forall (a :: Constraint). a => Dict a
Dict
instance Monoid w => Lifting (MonadState s) (Strict.WriterT w) where lifting :: forall (a :: * -> *). MonadState s a :- MonadState s (WriterT w a)
lifting = (MonadState s a => Dict (MonadState s (WriterT w a)))
-> MonadState s a :- MonadState s (WriterT w a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadState s (WriterT w a))
MonadState s a => Dict (MonadState s (WriterT w a))
forall (a :: Constraint). a => Dict a
Dict
instance Monoid w => Lifting (MonadState s) (Lazy.WriterT w) where lifting :: forall (a :: * -> *). MonadState s a :- MonadState s (WriterT w a)
lifting = (MonadState s a => Dict (MonadState s (WriterT w a)))
-> MonadState s a :- MonadState s (WriterT w a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadState s (WriterT w a))
MonadState s a => Dict (MonadState s (WriterT w a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting (MonadState s) (ReaderT r) where lifting :: forall (a :: * -> *). MonadState s a :- MonadState s (ReaderT r a)
lifting = (MonadState s a => Dict (MonadState s (ReaderT r a)))
-> MonadState s a :- MonadState s (ReaderT r a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadState s (ReaderT r a))
MonadState s a => Dict (MonadState s (ReaderT r a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting (MonadState s) (ExceptT e) where lifting :: forall (a :: * -> *). MonadState s a :- MonadState s (ExceptT e a)
lifting = (MonadState s a => Dict (MonadState s (ExceptT e a)))
-> MonadState s a :- MonadState s (ExceptT e a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadState s (ExceptT e a))
MonadState s a => Dict (MonadState s (ExceptT e a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting (MonadState s) (ContT r') where lifting :: forall (a :: * -> *). MonadState s a :- MonadState s (ContT r' a)
lifting = (MonadState s a => Dict (MonadState s (ContT r' a)))
-> MonadState s a :- MonadState s (ContT r' a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (MonadState s (ContT r' a))
MonadState s a => Dict (MonadState s (ContT r' a))
forall (a :: Constraint). a => Dict a
Dict

class Lifting2 p f where
  lifting2 :: p a :- Lifting p (f a) -- (p a, p b) :- p (f a b)

instance Lifting2 Eq Either where lifting2 :: forall a. Eq a :- Lifting Eq (Either a)
lifting2 = (Eq a => Dict (Lifting Eq (Either a)))
-> Eq a :- Lifting Eq (Either a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting Eq (Either a))
Eq a => Dict (Lifting Eq (Either a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting2 Ord Either where lifting2 :: forall a. Ord a :- Lifting Ord (Either a)
lifting2 = (Ord a => Dict (Lifting Ord (Either a)))
-> Ord a :- Lifting Ord (Either a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting Ord (Either a))
Ord a => Dict (Lifting Ord (Either a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting2 Show Either where lifting2 :: forall a. Show a :- Lifting Show (Either a)
lifting2 = (Show a => Dict (Lifting Show (Either a)))
-> Show a :- Lifting Show (Either a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting Show (Either a))
Show a => Dict (Lifting Show (Either a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting2 Read Either where lifting2 :: forall a. Read a :- Lifting Read (Either a)
lifting2 = (Read a => Dict (Lifting Read (Either a)))
-> Read a :- Lifting Read (Either a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting Read (Either a))
Read a => Dict (Lifting Read (Either a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting2 Hashable Either where lifting2 :: forall a. Hashable a :- Lifting Hashable (Either a)
lifting2 = (Hashable a => Dict (Lifting Hashable (Either a)))
-> Hashable a :- Lifting Hashable (Either a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting Hashable (Either a))
Hashable a => Dict (Lifting Hashable (Either a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting2 Binary Either where lifting2 :: forall a. Binary a :- Lifting Binary (Either a)
lifting2 = (Binary a => Dict (Lifting Binary (Either a)))
-> Binary a :- Lifting Binary (Either a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting Binary (Either a))
Binary a => Dict (Lifting Binary (Either a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting2 NFData Either where lifting2 :: forall a. NFData a :- Lifting NFData (Either a)
lifting2 = (NFData a => Dict (Lifting NFData (Either a)))
-> NFData a :- Lifting NFData (Either a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting NFData (Either a))
NFData a => Dict (Lifting NFData (Either a))
forall (a :: Constraint). a => Dict a
Dict

instance Lifting2 Eq (,) where lifting2 :: forall a. Eq a :- Lifting Eq ((,) a)
lifting2 = (Eq a => Dict (Lifting Eq ((,) a))) -> Eq a :- Lifting Eq ((,) a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting Eq ((,) a))
Eq a => Dict (Lifting Eq ((,) a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting2 Ord (,) where lifting2 :: forall a. Ord a :- Lifting Ord ((,) a)
lifting2 = (Ord a => Dict (Lifting Ord ((,) a)))
-> Ord a :- Lifting Ord ((,) a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting Ord ((,) a))
Ord a => Dict (Lifting Ord ((,) a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting2 Show (,) where lifting2 :: forall a. Show a :- Lifting Show ((,) a)
lifting2 = (Show a => Dict (Lifting Show ((,) a)))
-> Show a :- Lifting Show ((,) a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting Show ((,) a))
Show a => Dict (Lifting Show ((,) a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting2 Read (,) where lifting2 :: forall a. Read a :- Lifting Read ((,) a)
lifting2 = (Read a => Dict (Lifting Read ((,) a)))
-> Read a :- Lifting Read ((,) a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting Read ((,) a))
Read a => Dict (Lifting Read ((,) a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting2 Hashable (,) where lifting2 :: forall a. Hashable a :- Lifting Hashable ((,) a)
lifting2 = (Hashable a => Dict (Lifting Hashable ((,) a)))
-> Hashable a :- Lifting Hashable ((,) a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting Hashable ((,) a))
Hashable a => Dict (Lifting Hashable ((,) a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting2 Binary (,) where lifting2 :: forall a. Binary a :- Lifting Binary ((,) a)
lifting2 = (Binary a => Dict (Lifting Binary ((,) a)))
-> Binary a :- Lifting Binary ((,) a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting Binary ((,) a))
Binary a => Dict (Lifting Binary ((,) a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting2 NFData (,) where lifting2 :: forall a. NFData a :- Lifting NFData ((,) a)
lifting2 = (NFData a => Dict (Lifting NFData ((,) a)))
-> NFData a :- Lifting NFData ((,) a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting NFData ((,) a))
NFData a => Dict (Lifting NFData ((,) a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting2 Semigroup (,) where lifting2 :: forall a. Semigroup a :- Lifting Semigroup ((,) a)
lifting2 = (Semigroup a => Dict (Lifting Semigroup ((,) a)))
-> Semigroup a :- Lifting Semigroup ((,) a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting Semigroup ((,) a))
Semigroup a => Dict (Lifting Semigroup ((,) a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting2 Monoid (,) where lifting2 :: forall a. Monoid a :- Lifting Monoid ((,) a)
lifting2 = (Monoid a => Dict (Lifting Monoid ((,) a)))
-> Monoid a :- Lifting Monoid ((,) a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting Monoid ((,) a))
Monoid a => Dict (Lifting Monoid ((,) a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting2 Bounded (,) where lifting2 :: forall a. Bounded a :- Lifting Bounded ((,) a)
lifting2 = (Bounded a => Dict (Lifting Bounded ((,) a)))
-> Bounded a :- Lifting Bounded ((,) a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting Bounded ((,) a))
Bounded a => Dict (Lifting Bounded ((,) a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting2 Ix (,) where lifting2 :: forall a. Ix a :- Lifting Ix ((,) a)
lifting2 = (Ix a => Dict (Lifting Ix ((,) a))) -> Ix a :- Lifting Ix ((,) a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting Ix ((,) a))
Ix a => Dict (Lifting Ix ((,) a))
forall (a :: Constraint). a => Dict a
Dict

instance Lifting2 Functor Compose where lifting2 :: forall (a :: * -> *). Functor a :- Lifting Functor (Compose a)
lifting2 = (Functor a => Dict (Lifting Functor (Compose a)))
-> Functor a :- Lifting Functor (Compose a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting Functor (Compose a))
Functor a => Dict (Lifting Functor (Compose a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting2 Foldable Compose where lifting2 :: forall (a :: * -> *). Foldable a :- Lifting Foldable (Compose a)
lifting2 = (Foldable a => Dict (Lifting Foldable (Compose a)))
-> Foldable a :- Lifting Foldable (Compose a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting Foldable (Compose a))
Foldable a => Dict (Lifting Foldable (Compose a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting2 Traversable Compose where lifting2 :: forall (a :: * -> *).
Traversable a :- Lifting Traversable (Compose a)
lifting2 = (Traversable a => Dict (Lifting Traversable (Compose a)))
-> Traversable a :- Lifting Traversable (Compose a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting Traversable (Compose a))
Traversable a => Dict (Lifting Traversable (Compose a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting2 Applicative Compose where lifting2 :: forall (a :: * -> *).
Applicative a :- Lifting Applicative (Compose a)
lifting2 = (Applicative a => Dict (Lifting Applicative (Compose a)))
-> Applicative a :- Lifting Applicative (Compose a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting Applicative (Compose a))
Applicative a => Dict (Lifting Applicative (Compose a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting2 Alternative Compose where lifting2 :: forall (a :: * -> *).
Alternative a :- Lifting Alternative (Compose a)
lifting2 = (Alternative a => Dict (Lifting Alternative (Compose a)))
-> Alternative a :- Lifting Alternative (Compose a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting Alternative (Compose a))
Alternative a => Dict (Lifting Alternative (Compose a))
forall (a :: Constraint). a => Dict a
Dict -- overconstrained

instance Lifting2 Functor Functor.Product where lifting2 :: forall (a :: * -> *). Functor a :- Lifting Functor (Product a)
lifting2 = (Functor a => Dict (Lifting Functor (Product a)))
-> Functor a :- Lifting Functor (Product a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting Functor (Product a))
Functor a => Dict (Lifting Functor (Product a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting2 Foldable Functor.Product where lifting2 :: forall (a :: * -> *). Foldable a :- Lifting Foldable (Product a)
lifting2 = (Foldable a => Dict (Lifting Foldable (Product a)))
-> Foldable a :- Lifting Foldable (Product a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting Foldable (Product a))
Foldable a => Dict (Lifting Foldable (Product a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting2 Traversable Functor.Product where lifting2 :: forall (a :: * -> *).
Traversable a :- Lifting Traversable (Product a)
lifting2 = (Traversable a => Dict (Lifting Traversable (Product a)))
-> Traversable a :- Lifting Traversable (Product a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting Traversable (Product a))
Traversable a => Dict (Lifting Traversable (Product a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting2 Applicative Functor.Product where lifting2 :: forall (a :: * -> *).
Applicative a :- Lifting Applicative (Product a)
lifting2 = (Applicative a => Dict (Lifting Applicative (Product a)))
-> Applicative a :- Lifting Applicative (Product a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting Applicative (Product a))
Applicative a => Dict (Lifting Applicative (Product a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting2 Alternative Functor.Product where lifting2 :: forall (a :: * -> *).
Alternative a :- Lifting Alternative (Product a)
lifting2 = (Alternative a => Dict (Lifting Alternative (Product a)))
-> Alternative a :- Lifting Alternative (Product a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting Alternative (Product a))
Alternative a => Dict (Lifting Alternative (Product a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting2 Monad Functor.Product where lifting2 :: forall (a :: * -> *). Monad a :- Lifting Monad (Product a)
lifting2 = (Monad a => Dict (Lifting Monad (Product a)))
-> Monad a :- Lifting Monad (Product a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting Monad (Product a))
Monad a => Dict (Lifting Monad (Product a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting2 MonadPlus Functor.Product where lifting2 :: forall (a :: * -> *). MonadPlus a :- Lifting MonadPlus (Product a)
lifting2 = (MonadPlus a => Dict (Lifting MonadPlus (Product a)))
-> MonadPlus a :- Lifting MonadPlus (Product a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting MonadPlus (Product a))
MonadPlus a => Dict (Lifting MonadPlus (Product a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting2 MonadFix Functor.Product where lifting2 :: forall (a :: * -> *). MonadFix a :- Lifting MonadFix (Product a)
lifting2 = (MonadFix a => Dict (Lifting MonadFix (Product a)))
-> MonadFix a :- Lifting MonadFix (Product a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting MonadFix (Product a))
MonadFix a => Dict (Lifting MonadFix (Product a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting2 Show1 Functor.Product where lifting2 :: forall (a :: * -> *). Show1 a :- Lifting Show1 (Product a)
lifting2 = (Show1 a => Dict (Lifting Show1 (Product a)))
-> Show1 a :- Lifting Show1 (Product a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting Show1 (Product a))
Show1 a => Dict (Lifting Show1 (Product a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting2 Eq1 Functor.Product where lifting2 :: forall (a :: * -> *). Eq1 a :- Lifting Eq1 (Product a)
lifting2 = (Eq1 a => Dict (Lifting Eq1 (Product a)))
-> Eq1 a :- Lifting Eq1 (Product a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting Eq1 (Product a))
Eq1 a => Dict (Lifting Eq1 (Product a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting2 Ord1 Functor.Product where lifting2 :: forall (a :: * -> *). Ord1 a :- Lifting Ord1 (Product a)
lifting2 = (Ord1 a => Dict (Lifting Ord1 (Product a)))
-> Ord1 a :- Lifting Ord1 (Product a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting Ord1 (Product a))
Ord1 a => Dict (Lifting Ord1 (Product a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting2 Read1 Functor.Product where lifting2 :: forall (a :: * -> *). Read1 a :- Lifting Read1 (Product a)
lifting2 = (Read1 a => Dict (Lifting Read1 (Product a)))
-> Read1 a :- Lifting Read1 (Product a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting Read1 (Product a))
Read1 a => Dict (Lifting Read1 (Product a))
forall (a :: Constraint). a => Dict a
Dict

instance Lifting2 Functor Functor.Sum where lifting2 :: forall (a :: * -> *). Functor a :- Lifting Functor (Sum a)
lifting2 = (Functor a => Dict (Lifting Functor (Sum a)))
-> Functor a :- Lifting Functor (Sum a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting Functor (Sum a))
Functor a => Dict (Lifting Functor (Sum a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting2 Foldable Functor.Sum where lifting2 :: forall (a :: * -> *). Foldable a :- Lifting Foldable (Sum a)
lifting2 = (Foldable a => Dict (Lifting Foldable (Sum a)))
-> Foldable a :- Lifting Foldable (Sum a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting Foldable (Sum a))
Foldable a => Dict (Lifting Foldable (Sum a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting2 Traversable Functor.Sum where lifting2 :: forall (a :: * -> *). Traversable a :- Lifting Traversable (Sum a)
lifting2 = (Traversable a => Dict (Lifting Traversable (Sum a)))
-> Traversable a :- Lifting Traversable (Sum a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting Traversable (Sum a))
Traversable a => Dict (Lifting Traversable (Sum a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting2 Show1 Functor.Sum where lifting2 :: forall (a :: * -> *). Show1 a :- Lifting Show1 (Sum a)
lifting2 = (Show1 a => Dict (Lifting Show1 (Sum a)))
-> Show1 a :- Lifting Show1 (Sum a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting Show1 (Sum a))
Show1 a => Dict (Lifting Show1 (Sum a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting2 Eq1 Functor.Sum where lifting2 :: forall (a :: * -> *). Eq1 a :- Lifting Eq1 (Sum a)
lifting2 = (Eq1 a => Dict (Lifting Eq1 (Sum a)))
-> Eq1 a :- Lifting Eq1 (Sum a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting Eq1 (Sum a))
Eq1 a => Dict (Lifting Eq1 (Sum a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting2 Ord1 Functor.Sum where lifting2 :: forall (a :: * -> *). Ord1 a :- Lifting Ord1 (Sum a)
lifting2 = (Ord1 a => Dict (Lifting Ord1 (Sum a)))
-> Ord1 a :- Lifting Ord1 (Sum a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting Ord1 (Sum a))
Ord1 a => Dict (Lifting Ord1 (Sum a))
forall (a :: Constraint). a => Dict a
Dict
instance Lifting2 Read1 Functor.Sum where lifting2 :: forall (a :: * -> *). Read1 a :- Lifting Read1 (Sum a)
lifting2 = (Read1 a => Dict (Lifting Read1 (Sum a)))
-> Read1 a :- Lifting Read1 (Sum a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Dict (Lifting Read1 (Sum a))
Read1 a => Dict (Lifting Read1 (Sum a))
forall (a :: Constraint). a => Dict a
Dict