{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE RoleAnnotations #-}
{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UnicodeSyntax #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ >= 706
{-# LANGUAGE PolyKinds #-}
#endif
#if __GLASGOW_HASKELL__ >= 800
{-# LANGUAGE TypeInType #-}
{-# LANGUAGE UndecidableSuperClasses #-}
#endif
#if __GLASGOW_HASKELL__ >= 708 && __GLASGOW_HASKELL__ < 710
{-# LANGUAGE NullaryTypeClasses #-}
#endif
#if __GLASGOW_HASKELL__ >= 806
{-# LANGUAGE QuantifiedConstraints #-}
#endif
module Data.Constraint
(
Constraint
, Dict(Dict)
, HasDict(..)
, withDict
, (\\)
, (:-)(Sub)
, type (⊢)
, weaken1, weaken2, contract
, strengthen1, strengthen2
, (&&&), (***)
, trans, refl
#if __GLASGOW_HASKELL__ >= 806
, implied
#endif
, Bottom(no)
, top, bottom
, mapDict
, unmapDict
, Class(..)
, (:=>)(..)
) where
import Control.Applicative
import Control.Category
import Control.DeepSeq
import Control.Monad
import Data.Complex
#if __GLASGOW_HASKELL__ >= 800 && __GLASGOW_HASKELL__ < 806
import Data.Kind
#endif
import Data.Ratio
#if !MIN_VERSION_base(4,11,0)
import Data.Semigroup
#endif
import Data.Data hiding (TypeRep)
import qualified GHC.Exts as Exts (Any)
import GHC.Exts (Constraint)
import Data.Bits (Bits)
import Data.Functor.Identity (Identity)
#if MIN_VERSION_base(4,8,0)
import Numeric.Natural (Natural)
#endif
#if !MIN_VERSION_base(4,8,0)
import Data.Word (Word)
#endif
import Data.Coerce (Coercible)
import Data.Type.Coercion(Coercion(..))
#if MIN_VERSION_base(4,9,0)
import Data.Type.Equality (type (~~))
import qualified Data.Type.Equality.Hetero as Hetero
#endif
#if MIN_VERSION_base(4,10,0)
import Type.Reflection (TypeRep, typeRepKind, withTypeable)
#endif
data Dict :: Constraint -> * where
Dict :: a => Dict a
deriving Typeable
instance (Typeable p, p) => Data (Dict p) where
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Dict p -> c (Dict p)
gfoldl forall d b. Data d => c (d -> b) -> d -> c b
_ forall g. g -> c g
z Dict p
Dict = Dict p -> c (Dict p)
forall g. g -> c g
z Dict p
forall (a :: Constraint). a => Dict a
Dict
toConstr :: Dict p -> Constr
toConstr Dict p
_ = Constr
dictConstr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Dict p)
gunfold forall b r. Data b => c (b -> r) -> c r
_ forall r. r -> c r
z Constr
c = case Constr -> Int
constrIndex Constr
c of
Int
1 -> Dict p -> c (Dict p)
forall r. r -> c r
z Dict p
forall (a :: Constraint). a => Dict a
Dict
Int
_ -> [Char] -> c (Dict p)
forall a. HasCallStack => [Char] -> a
error [Char]
"gunfold"
dataTypeOf :: Dict p -> DataType
dataTypeOf Dict p
_ = DataType
dictDataType
dictConstr :: Constr
dictConstr :: Constr
dictConstr = DataType -> [Char] -> [[Char]] -> Fixity -> Constr
mkConstr DataType
dictDataType [Char]
"Dict" [] Fixity
Prefix
dictDataType :: DataType
dictDataType :: DataType
dictDataType = [Char] -> [Constr] -> DataType
mkDataType [Char]
"Data.Constraint.Dict" [Constr
dictConstr]
deriving instance Eq (Dict a)
deriving instance Ord (Dict a)
deriving instance Show (Dict a)
instance NFData (Dict c) where
rnf :: Dict c -> ()
rnf Dict c
Dict = ()
class HasDict c e | e -> c where
evidence :: e -> Dict c
instance HasDict a (Dict a) where
evidence :: Dict a -> Dict a
evidence = Dict a -> Dict a
forall a. a -> a
Prelude.id
instance a => HasDict b (a :- b) where
evidence :: (a :- b) -> Dict b
evidence (Sub a => Dict b
x) = Dict b
a => Dict b
x
instance HasDict (Coercible a b) (Coercion a b) where
evidence :: Coercion a b -> Dict (Coercible a b)
evidence Coercion a b
Coercion = Dict (Coercible a b)
forall (a :: Constraint). a => Dict a
Dict
instance HasDict (a ~ b) (a :~: b) where
evidence :: (a :~: b) -> Dict (a ~ b)
evidence a :~: b
Refl = Dict (a ~ b)
forall (a :: Constraint). a => Dict a
Dict
#if MIN_VERSION_base(4,9,0)
instance HasDict (a ~~ b) (a Hetero.:~~: b) where
evidence :: (a :~~: b) -> Dict (a ~~ b)
evidence a :~~: b
Hetero.HRefl = Dict (a ~~ b)
forall (a :: Constraint). a => Dict a
Dict
#endif
#if MIN_VERSION_base(4,10,0)
instance HasDict (Typeable k, Typeable a) (TypeRep (a :: k)) where
evidence :: TypeRep a -> Dict (Typeable k, Typeable a)
evidence TypeRep a
tr = TypeRep a
-> (Typeable a => Dict (Typeable k, Typeable a))
-> Dict (Typeable k, Typeable a)
forall k (a :: k) r. TypeRep a -> (Typeable a => r) -> r
withTypeable TypeRep a
tr ((Typeable a => Dict (Typeable k, Typeable a))
-> Dict (Typeable k, Typeable a))
-> (Typeable a => Dict (Typeable k, Typeable a))
-> Dict (Typeable k, Typeable a)
forall a b. (a -> b) -> a -> b
$ TypeRep k
-> (Typeable k => Dict (Typeable k, Typeable a))
-> Dict (Typeable k, Typeable a)
forall k (a :: k) r. TypeRep a -> (Typeable a => r) -> r
withTypeable (TypeRep a -> TypeRep k
forall k (a :: k). TypeRep a -> TypeRep k
typeRepKind TypeRep a
tr) Typeable k => Dict (Typeable k, Typeable a)
forall (a :: Constraint). a => Dict a
Dict
#endif
withDict :: HasDict c e => e -> (c => r) -> r
withDict :: e -> (c => r) -> r
withDict e
d c => r
r = case e -> Dict c
forall (c :: Constraint) e. HasDict c e => e -> Dict c
evidence e
d of
Dict c
Dict -> r
c => r
r
infixl 1 \\
(\\) :: HasDict c e => (c => r) -> e -> r
c => r
r \\ :: (c => r) -> e -> r
\\ e
d = e -> (c => r) -> r
forall (c :: Constraint) e r. HasDict c e => e -> (c => r) -> r
withDict e
d c => r
r
infixr 9 :-
infixr 9 ⊢
type (⊢) = (:-)
newtype a :- b = Sub (a => Dict b)
deriving Typeable
type role (:-) nominal nominal
instance (Typeable p, Typeable q, p, q) => Data (p :- q) where
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> (p :- q) -> c (p :- q)
gfoldl forall d b. Data d => c (d -> b) -> d -> c b
_ forall g. g -> c g
z (Sub p => Dict q
Dict) = (p :- q) -> c (p :- q)
forall g. g -> c g
z ((p => Dict q) -> p :- q
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub p => Dict q
forall (a :: Constraint). a => Dict a
Dict)
toConstr :: (p :- q) -> Constr
toConstr p :- q
_ = Constr
subConstr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (p :- q)
gunfold forall b r. Data b => c (b -> r) -> c r
_ forall r. r -> c r
z Constr
c = case Constr -> Int
constrIndex Constr
c of
Int
1 -> (p :- q) -> c (p :- q)
forall r. r -> c r
z ((p => Dict q) -> p :- q
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub p => Dict q
forall (a :: Constraint). a => Dict a
Dict)
Int
_ -> [Char] -> c (p :- q)
forall a. HasCallStack => [Char] -> a
error [Char]
"gunfold"
dataTypeOf :: (p :- q) -> DataType
dataTypeOf p :- q
_ = DataType
subDataType
subConstr :: Constr
subConstr :: Constr
subConstr = DataType -> [Char] -> [[Char]] -> Fixity -> Constr
mkConstr DataType
dictDataType [Char]
"Sub" [] Fixity
Prefix
subDataType :: DataType
subDataType :: DataType
subDataType = [Char] -> [Constr] -> DataType
mkDataType [Char]
"Data.Constraint.:-" [Constr
subConstr]
instance Category (:-) where
id :: a :- a
id = a :- a
forall (a :: Constraint). a :- a
refl
. :: (b :- c) -> (a :- b) -> a :- c
(.) = (b :- c) -> (a :- b) -> a :- c
forall (b :: Constraint) (c :: Constraint) (a :: Constraint).
(b :- c) -> (a :- b) -> a :- c
trans
instance Eq (a :- b) where
a :- b
_ == :: (a :- b) -> (a :- b) -> Bool
== a :- b
_ = Bool
True
instance Ord (a :- b) where
compare :: (a :- b) -> (a :- b) -> Ordering
compare a :- b
_ a :- b
_ = Ordering
EQ
instance Show (a :- b) where
showsPrec :: Int -> (a :- b) -> ShowS
showsPrec Int
d a :- b
_ = Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) (ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ [Char] -> ShowS
showString [Char]
"Sub Dict"
instance a => NFData (a :- b) where
rnf :: (a :- b) -> ()
rnf (Sub a => Dict b
Dict) = ()
trans :: (b :- c) -> (a :- b) -> a :- c
trans :: (b :- c) -> (a :- b) -> a :- c
trans b :- c
f a :- b
g = (a => Dict c) -> a :- c
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub ((a => Dict c) -> a :- c) -> (a => Dict c) -> a :- c
forall a b. (a -> b) -> a -> b
$ c => Dict c
forall (a :: Constraint). a => Dict a
Dict (c => Dict c) -> (b :- c) -> Dict c
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ b :- c
f (b => Dict c) -> (a :- b) -> Dict c
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ a :- b
g
refl :: a :- a
refl :: a :- a
refl = (a => Dict a) -> a :- a
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub a => Dict a
forall (a :: Constraint). a => Dict a
Dict
#if __GLASGOW_HASKELL__ >= 806
implied :: forall a b. (a => b) => a :- b
implied :: a :- b
implied = (a => Dict b) -> a :- b
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (Dict b
forall (a :: Constraint). a => Dict a
Dict :: Dict b)
#endif
(***) :: (a :- b) -> (c :- d) -> (a, c) :- (b, d)
a :- b
f *** :: (a :- b) -> (c :- d) -> (a, c) :- (b, d)
*** c :- d
g = ((a, c) => Dict (b, d)) -> (a, c) :- (b, d)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (((a, c) => Dict (b, d)) -> (a, c) :- (b, d))
-> ((a, c) => Dict (b, d)) -> (a, c) :- (b, d)
forall a b. (a -> b) -> a -> b
$ b => Dict (b, d)
forall (a :: Constraint). a => Dict a
Dict (b => Dict (b, d)) -> (a :- b) -> Dict (b, d)
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ a :- b
f (d => Dict (b, d)) -> (c :- d) -> Dict (b, d)
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ c :- d
g
weaken1 :: (a, b) :- a
weaken1 :: (a, b) :- a
weaken1 = ((a, b) => Dict a) -> (a, b) :- a
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (a, b) => Dict a
forall (a :: Constraint). a => Dict a
Dict
weaken2 :: (a, b) :- b
weaken2 :: (a, b) :- b
weaken2 = ((a, b) => Dict b) -> (a, b) :- b
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (a, b) => Dict b
forall (a :: Constraint). a => Dict a
Dict
strengthen1 :: Dict b -> a :- c -> a :- (b,c)
strengthen1 :: Dict b -> (a :- c) -> a :- (b, c)
strengthen1 Dict b
d a :- c
e = (Dict a -> Dict b) -> a :- b
forall (a :: Constraint) (b :: Constraint).
(Dict a -> Dict b) -> a :- b
unmapDict (Dict b -> Dict a -> Dict b
forall a b. a -> b -> a
const Dict b
d) (a :- b) -> (a :- c) -> a :- (b, c)
forall (a :: Constraint) (b :: Constraint) (c :: Constraint).
(a :- b) -> (a :- c) -> a :- (b, c)
&&& a :- c
e
strengthen2 :: Dict b -> a :- c -> a :- (c,b)
strengthen2 :: Dict b -> (a :- c) -> a :- (c, b)
strengthen2 Dict b
d a :- c
e = a :- c
e (a :- c) -> (a :- b) -> a :- (c, b)
forall (a :: Constraint) (b :: Constraint) (c :: Constraint).
(a :- b) -> (a :- c) -> a :- (b, c)
&&& (Dict a -> Dict b) -> a :- b
forall (a :: Constraint) (b :: Constraint).
(Dict a -> Dict b) -> a :- b
unmapDict (Dict b -> Dict a -> Dict b
forall a b. a -> b -> a
const Dict b
d)
contract :: a :- (a, a)
contract :: a :- (a, a)
contract = (a => Dict (a, a)) -> a :- (a, a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub a => Dict (a, a)
forall (a :: Constraint). a => Dict a
Dict
(&&&) :: (a :- b) -> (a :- c) -> a :- (b, c)
a :- b
f &&& :: (a :- b) -> (a :- c) -> a :- (b, c)
&&& a :- c
g = (a => Dict (b, c)) -> a :- (b, c)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub ((a => Dict (b, c)) -> a :- (b, c))
-> (a => Dict (b, c)) -> a :- (b, c)
forall a b. (a -> b) -> a -> b
$ b => Dict (b, c)
forall (a :: Constraint). a => Dict a
Dict (b => Dict (b, c)) -> (a :- b) -> Dict (b, c)
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ a :- b
f (c => Dict (b, c)) -> (a :- c) -> Dict (b, c)
forall (c :: Constraint) e r. HasDict c e => (c => r) -> e -> r
\\ a :- c
g
top :: a :- ()
top :: a :- (() :: Constraint)
top = (a => Dict (() :: Constraint)) -> a :- (() :: Constraint)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub a => Dict (() :: Constraint)
forall (a :: Constraint). a => Dict a
Dict
class Exts.Any => Bottom where
no :: a
bottom :: Bottom :- a
bottom :: Bottom :- a
bottom = (Bottom => Dict a) -> Bottom :- a
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Bottom => Dict a
forall a. Bottom => a
no
mapDict :: (a :- b) -> Dict a -> Dict b
mapDict :: (a :- b) -> Dict a -> Dict b
mapDict a :- b
p Dict a
Dict = case a :- b
p of Sub a => Dict b
q -> Dict b
a => Dict b
q
unmapDict :: (Dict a -> Dict b) -> a :- b
unmapDict :: (Dict a -> Dict b) -> a :- b
unmapDict Dict a -> Dict b
f = (a => Dict b) -> a :- b
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (Dict a -> Dict b
f Dict a
forall (a :: Constraint). a => Dict a
Dict)
type role Dict nominal
class Class b h | h -> b where
cls :: h :- b
infixr 9 :=>
class b :=> h | h -> b where
ins :: b :- h
instance Class () (Class b a) where cls :: Class b a :- (() :: Constraint)
cls = (Class b a => Dict (() :: Constraint))
-> Class b a :- (() :: Constraint)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Class b a => Dict (() :: Constraint)
forall (a :: Constraint). a => Dict a
Dict
instance Class () (b :=> a) where cls :: (b :=> a) :- (() :: Constraint)
cls = ((b :=> a) => Dict (() :: Constraint))
-> (b :=> a) :- (() :: Constraint)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (b :=> a) => Dict (() :: Constraint)
forall (a :: Constraint). a => Dict a
Dict
instance Class b a => () :=> Class b a where ins :: (() :: Constraint) :- Class b a
ins = ((() :: Constraint) => Dict (Class b a))
-> (() :: Constraint) :- Class b a
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Class b a)
forall (a :: Constraint). a => Dict a
Dict
instance (b :=> a) => () :=> (b :=> a) where ins :: (() :: Constraint) :- (b :=> a)
ins = ((() :: Constraint) => Dict (b :=> a))
-> (() :: Constraint) :- (b :=> a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (b :=> a)
forall (a :: Constraint). a => Dict a
Dict
instance Class () () where cls :: (() :: Constraint) :- (() :: Constraint)
cls = ((() :: Constraint) => Dict (() :: Constraint))
-> (() :: Constraint) :- (() :: Constraint)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (() :: Constraint)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> () where ins :: (() :: Constraint) :- (() :: Constraint)
ins = ((() :: Constraint) => Dict (() :: Constraint))
-> (() :: Constraint) :- (() :: Constraint)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (() :: Constraint)
forall (a :: Constraint). a => Dict a
Dict
instance Class () (Eq a) where cls :: Eq a :- (() :: Constraint)
cls = (Eq a => Dict (() :: Constraint)) -> Eq a :- (() :: Constraint)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Eq a => Dict (() :: Constraint)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Eq () where ins :: (() :: Constraint) :- Eq ()
ins = ((() :: Constraint) => Dict (Eq ())) -> (() :: Constraint) :- Eq ()
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Eq ())
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Eq Int where ins :: (() :: Constraint) :- Eq Int
ins = ((() :: Constraint) => Dict (Eq Int))
-> (() :: Constraint) :- Eq Int
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Eq Int)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Eq Bool where ins :: (() :: Constraint) :- Eq Bool
ins = ((() :: Constraint) => Dict (Eq Bool))
-> (() :: Constraint) :- Eq Bool
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Eq Bool)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Eq Integer where ins :: (() :: Constraint) :- Eq Integer
ins = ((() :: Constraint) => Dict (Eq Integer))
-> (() :: Constraint) :- Eq Integer
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Eq Integer)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Eq Float where ins :: (() :: Constraint) :- Eq Float
ins = ((() :: Constraint) => Dict (Eq Float))
-> (() :: Constraint) :- Eq Float
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Eq Float)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Eq Double where ins :: (() :: Constraint) :- Eq Double
ins = ((() :: Constraint) => Dict (Eq Double))
-> (() :: Constraint) :- Eq Double
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Eq Double)
forall (a :: Constraint). a => Dict a
Dict
instance Eq a :=> Eq [a] where ins :: Eq a :- Eq [a]
ins = (Eq a => Dict (Eq [a])) -> Eq a :- Eq [a]
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Eq a => Dict (Eq [a])
forall (a :: Constraint). a => Dict a
Dict
instance Eq a :=> Eq (Maybe a) where ins :: Eq a :- Eq (Maybe a)
ins = (Eq a => Dict (Eq (Maybe a))) -> Eq a :- Eq (Maybe a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Eq a => Dict (Eq (Maybe a))
forall (a :: Constraint). a => Dict a
Dict
instance Eq a :=> Eq (Complex a) where ins :: Eq a :- Eq (Complex a)
ins = (Eq a => Dict (Eq (Complex a))) -> Eq a :- Eq (Complex a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Eq a => Dict (Eq (Complex a))
forall (a :: Constraint). a => Dict a
Dict
instance Eq a :=> Eq (Ratio a) where ins :: Eq a :- Eq (Ratio a)
ins = (Eq a => Dict (Eq (Ratio a))) -> Eq a :- Eq (Ratio a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Eq a => Dict (Eq (Ratio a))
forall (a :: Constraint). a => Dict a
Dict
instance (Eq a, Eq b) :=> Eq (a, b) where ins :: (Eq a, Eq b) :- Eq (a, b)
ins = ((Eq a, Eq b) => Dict (Eq (a, b))) -> (Eq a, Eq b) :- Eq (a, b)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (Eq a, Eq b) => Dict (Eq (a, b))
forall (a :: Constraint). a => Dict a
Dict
instance (Eq a, Eq b) :=> Eq (Either a b) where ins :: (Eq a, Eq b) :- Eq (Either a b)
ins = ((Eq a, Eq b) => Dict (Eq (Either a b)))
-> (Eq a, Eq b) :- Eq (Either a b)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (Eq a, Eq b) => Dict (Eq (Either a b))
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Eq (Dict a) where ins :: (() :: Constraint) :- Eq (Dict a)
ins = ((() :: Constraint) => Dict (Eq (Dict a)))
-> (() :: Constraint) :- Eq (Dict a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Eq (Dict a))
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Eq (a :- b) where ins :: (() :: Constraint) :- Eq (a :- b)
ins = ((() :: Constraint) => Dict (Eq (a :- b)))
-> (() :: Constraint) :- Eq (a :- b)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Eq (a :- b))
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Eq Word where ins :: (() :: Constraint) :- Eq Word
ins = ((() :: Constraint) => Dict (Eq Word))
-> (() :: Constraint) :- Eq Word
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Eq Word)
forall (a :: Constraint). a => Dict a
Dict
instance Eq a :=> Eq (Identity a) where ins :: Eq a :- Eq (Identity a)
ins = (Eq a => Dict (Eq (Identity a))) -> Eq a :- Eq (Identity a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Eq a => Dict (Eq (Identity a))
forall (a :: Constraint). a => Dict a
Dict
#if MIN_VERSION_base(4,8,0)
instance Eq a :=> Eq (Const a b) where ins :: Eq a :- Eq (Const a b)
ins = (Eq a => Dict (Eq (Const a b))) -> Eq a :- Eq (Const a b)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Eq a => Dict (Eq (Const a b))
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Eq Natural where ins :: (() :: Constraint) :- Eq Natural
ins = ((() :: Constraint) => Dict (Eq Natural))
-> (() :: Constraint) :- Eq Natural
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Eq Natural)
forall (a :: Constraint). a => Dict a
Dict
#endif
instance Class (Eq a) (Ord a) where cls :: Ord a :- Eq a
cls = (Ord a => Dict (Eq a)) -> Ord a :- Eq a
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Ord a => Dict (Eq a)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Ord () where ins :: (() :: Constraint) :- Ord ()
ins = ((() :: Constraint) => Dict (Ord ()))
-> (() :: Constraint) :- Ord ()
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Ord ())
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Ord Bool where ins :: (() :: Constraint) :- Ord Bool
ins = ((() :: Constraint) => Dict (Ord Bool))
-> (() :: Constraint) :- Ord Bool
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Ord Bool)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Ord Int where ins :: (() :: Constraint) :- Ord Int
ins = ((() :: Constraint) => Dict (Ord Int))
-> (() :: Constraint) :- Ord Int
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Ord Int)
forall (a :: Constraint). a => Dict a
Dict
instance ():=> Ord Integer where ins :: (() :: Constraint) :- Ord Integer
ins = ((() :: Constraint) => Dict (Ord Integer))
-> (() :: Constraint) :- Ord Integer
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Ord Integer)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Ord Float where ins :: (() :: Constraint) :- Ord Float
ins = ((() :: Constraint) => Dict (Ord Float))
-> (() :: Constraint) :- Ord Float
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Ord Float)
forall (a :: Constraint). a => Dict a
Dict
instance ():=> Ord Double where ins :: (() :: Constraint) :- Ord Double
ins = ((() :: Constraint) => Dict (Ord Double))
-> (() :: Constraint) :- Ord Double
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Ord Double)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Ord Char where ins :: (() :: Constraint) :- Ord Char
ins = ((() :: Constraint) => Dict (Ord Char))
-> (() :: Constraint) :- Ord Char
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Ord Char)
forall (a :: Constraint). a => Dict a
Dict
instance Ord a :=> Ord (Maybe a) where ins :: Ord a :- Ord (Maybe a)
ins = (Ord a => Dict (Ord (Maybe a))) -> Ord a :- Ord (Maybe a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Ord a => Dict (Ord (Maybe a))
forall (a :: Constraint). a => Dict a
Dict
instance Ord a :=> Ord [a] where ins :: Ord a :- Ord [a]
ins = (Ord a => Dict (Ord [a])) -> Ord a :- Ord [a]
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Ord a => Dict (Ord [a])
forall (a :: Constraint). a => Dict a
Dict
instance (Ord a, Ord b) :=> Ord (a, b) where ins :: (Ord a, Ord b) :- Ord (a, b)
ins = ((Ord a, Ord b) => Dict (Ord (a, b)))
-> (Ord a, Ord b) :- Ord (a, b)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (Ord a, Ord b) => Dict (Ord (a, b))
forall (a :: Constraint). a => Dict a
Dict
instance (Ord a, Ord b) :=> Ord (Either a b) where ins :: (Ord a, Ord b) :- Ord (Either a b)
ins = ((Ord a, Ord b) => Dict (Ord (Either a b)))
-> (Ord a, Ord b) :- Ord (Either a b)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (Ord a, Ord b) => Dict (Ord (Either a b))
forall (a :: Constraint). a => Dict a
Dict
instance Integral a :=> Ord (Ratio a) where ins :: Integral a :- Ord (Ratio a)
ins = (Integral a => Dict (Ord (Ratio a))) -> Integral a :- Ord (Ratio a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Integral a => Dict (Ord (Ratio a))
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Ord (Dict a) where ins :: (() :: Constraint) :- Ord (Dict a)
ins = ((() :: Constraint) => Dict (Ord (Dict a)))
-> (() :: Constraint) :- Ord (Dict a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Ord (Dict a))
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Ord (a :- b) where ins :: (() :: Constraint) :- Ord (a :- b)
ins = ((() :: Constraint) => Dict (Ord (a :- b)))
-> (() :: Constraint) :- Ord (a :- b)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Ord (a :- b))
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Ord Word where ins :: (() :: Constraint) :- Ord Word
ins = ((() :: Constraint) => Dict (Ord Word))
-> (() :: Constraint) :- Ord Word
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Ord Word)
forall (a :: Constraint). a => Dict a
Dict
instance Ord a :=> Ord (Identity a) where ins :: Ord a :- Ord (Identity a)
ins = (Ord a => Dict (Ord (Identity a))) -> Ord a :- Ord (Identity a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Ord a => Dict (Ord (Identity a))
forall (a :: Constraint). a => Dict a
Dict
#if MIN_VERSION_base(4,8,0)
instance Ord a :=> Ord (Const a b) where ins :: Ord a :- Ord (Const a b)
ins = (Ord a => Dict (Ord (Const a b))) -> Ord a :- Ord (Const a b)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Ord a => Dict (Ord (Const a b))
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Ord Natural where ins :: (() :: Constraint) :- Ord Natural
ins = ((() :: Constraint) => Dict (Ord Natural))
-> (() :: Constraint) :- Ord Natural
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Ord Natural)
forall (a :: Constraint). a => Dict a
Dict
#endif
instance Class () (Show a) where cls :: Show a :- (() :: Constraint)
cls = (Show a => Dict (() :: Constraint)) -> Show a :- (() :: Constraint)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Show a => Dict (() :: Constraint)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Show () where ins :: (() :: Constraint) :- Show ()
ins = ((() :: Constraint) => Dict (Show ()))
-> (() :: Constraint) :- Show ()
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Show ())
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Show Bool where ins :: (() :: Constraint) :- Show Bool
ins = ((() :: Constraint) => Dict (Show Bool))
-> (() :: Constraint) :- Show Bool
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Show Bool)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Show Ordering where ins :: (() :: Constraint) :- Show Ordering
ins = ((() :: Constraint) => Dict (Show Ordering))
-> (() :: Constraint) :- Show Ordering
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Show Ordering)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Show Char where ins :: (() :: Constraint) :- Show Char
ins = ((() :: Constraint) => Dict (Show Char))
-> (() :: Constraint) :- Show Char
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Show Char)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Show Int where ins :: (() :: Constraint) :- Show Int
ins = ((() :: Constraint) => Dict (Show Int))
-> (() :: Constraint) :- Show Int
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Show Int)
forall (a :: Constraint). a => Dict a
Dict
instance Show a :=> Show (Complex a) where ins :: Show a :- Show (Complex a)
ins = (Show a => Dict (Show (Complex a))) -> Show a :- Show (Complex a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Show a => Dict (Show (Complex a))
forall (a :: Constraint). a => Dict a
Dict
instance Show a :=> Show [a] where ins :: Show a :- Show [a]
ins = (Show a => Dict (Show [a])) -> Show a :- Show [a]
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Show a => Dict (Show [a])
forall (a :: Constraint). a => Dict a
Dict
instance Show a :=> Show (Maybe a) where ins :: Show a :- Show (Maybe a)
ins = (Show a => Dict (Show (Maybe a))) -> Show a :- Show (Maybe a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Show a => Dict (Show (Maybe a))
forall (a :: Constraint). a => Dict a
Dict
instance (Show a, Show b) :=> Show (a, b) where ins :: (Show a, Show b) :- Show (a, b)
ins = ((Show a, Show b) => Dict (Show (a, b)))
-> (Show a, Show b) :- Show (a, b)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (Show a, Show b) => Dict (Show (a, b))
forall (a :: Constraint). a => Dict a
Dict
instance (Show a, Show b) :=> Show (Either a b) where ins :: (Show a, Show b) :- Show (Either a b)
ins = ((Show a, Show b) => Dict (Show (Either a b)))
-> (Show a, Show b) :- Show (Either a b)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (Show a, Show b) => Dict (Show (Either a b))
forall (a :: Constraint). a => Dict a
Dict
instance (Integral a, Show a) :=> Show (Ratio a) where ins :: (Integral a, Show a) :- Show (Ratio a)
ins = ((Integral a, Show a) => Dict (Show (Ratio a)))
-> (Integral a, Show a) :- Show (Ratio a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (Integral a, Show a) => Dict (Show (Ratio a))
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Show (Dict a) where ins :: (() :: Constraint) :- Show (Dict a)
ins = ((() :: Constraint) => Dict (Show (Dict a)))
-> (() :: Constraint) :- Show (Dict a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Show (Dict a))
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Show (a :- b) where ins :: (() :: Constraint) :- Show (a :- b)
ins = ((() :: Constraint) => Dict (Show (a :- b)))
-> (() :: Constraint) :- Show (a :- b)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Show (a :- b))
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Show Word where ins :: (() :: Constraint) :- Show Word
ins = ((() :: Constraint) => Dict (Show Word))
-> (() :: Constraint) :- Show Word
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Show Word)
forall (a :: Constraint). a => Dict a
Dict
instance Show a :=> Show (Identity a) where ins :: Show a :- Show (Identity a)
ins = (Show a => Dict (Show (Identity a))) -> Show a :- Show (Identity a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Show a => Dict (Show (Identity a))
forall (a :: Constraint). a => Dict a
Dict
#if MIN_VERSION_base(4,8,0)
instance Show a :=> Show (Const a b) where ins :: Show a :- Show (Const a b)
ins = (Show a => Dict (Show (Const a b))) -> Show a :- Show (Const a b)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Show a => Dict (Show (Const a b))
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Show Natural where ins :: (() :: Constraint) :- Show Natural
ins = ((() :: Constraint) => Dict (Show Natural))
-> (() :: Constraint) :- Show Natural
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Show Natural)
forall (a :: Constraint). a => Dict a
Dict
#endif
instance Class () (Read a) where cls :: Read a :- (() :: Constraint)
cls = (Read a => Dict (() :: Constraint)) -> Read a :- (() :: Constraint)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Read a => Dict (() :: Constraint)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Read () where ins :: (() :: Constraint) :- Read ()
ins = ((() :: Constraint) => Dict (Read ()))
-> (() :: Constraint) :- Read ()
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Read ())
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Read Bool where ins :: (() :: Constraint) :- Read Bool
ins = ((() :: Constraint) => Dict (Read Bool))
-> (() :: Constraint) :- Read Bool
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Read Bool)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Read Ordering where ins :: (() :: Constraint) :- Read Ordering
ins = ((() :: Constraint) => Dict (Read Ordering))
-> (() :: Constraint) :- Read Ordering
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Read Ordering)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Read Char where ins :: (() :: Constraint) :- Read Char
ins = ((() :: Constraint) => Dict (Read Char))
-> (() :: Constraint) :- Read Char
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Read Char)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Read Int where ins :: (() :: Constraint) :- Read Int
ins = ((() :: Constraint) => Dict (Read Int))
-> (() :: Constraint) :- Read Int
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Read Int)
forall (a :: Constraint). a => Dict a
Dict
instance Read a :=> Read (Complex a) where ins :: Read a :- Read (Complex a)
ins = (Read a => Dict (Read (Complex a))) -> Read a :- Read (Complex a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Read a => Dict (Read (Complex a))
forall (a :: Constraint). a => Dict a
Dict
instance Read a :=> Read [a] where ins :: Read a :- Read [a]
ins = (Read a => Dict (Read [a])) -> Read a :- Read [a]
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Read a => Dict (Read [a])
forall (a :: Constraint). a => Dict a
Dict
instance Read a :=> Read (Maybe a) where ins :: Read a :- Read (Maybe a)
ins = (Read a => Dict (Read (Maybe a))) -> Read a :- Read (Maybe a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Read a => Dict (Read (Maybe a))
forall (a :: Constraint). a => Dict a
Dict
instance (Read a, Read b) :=> Read (a, b) where ins :: (Read a, Read b) :- Read (a, b)
ins = ((Read a, Read b) => Dict (Read (a, b)))
-> (Read a, Read b) :- Read (a, b)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (Read a, Read b) => Dict (Read (a, b))
forall (a :: Constraint). a => Dict a
Dict
instance (Read a, Read b) :=> Read (Either a b) where ins :: (Read a, Read b) :- Read (Either a b)
ins = ((Read a, Read b) => Dict (Read (Either a b)))
-> (Read a, Read b) :- Read (Either a b)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (Read a, Read b) => Dict (Read (Either a b))
forall (a :: Constraint). a => Dict a
Dict
instance (Integral a, Read a) :=> Read (Ratio a) where ins :: (Integral a, Read a) :- Read (Ratio a)
ins = ((Integral a, Read a) => Dict (Read (Ratio a)))
-> (Integral a, Read a) :- Read (Ratio a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (Integral a, Read a) => Dict (Read (Ratio a))
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Read Word where ins :: (() :: Constraint) :- Read Word
ins = ((() :: Constraint) => Dict (Read Word))
-> (() :: Constraint) :- Read Word
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Read Word)
forall (a :: Constraint). a => Dict a
Dict
instance Read a :=> Read (Identity a) where ins :: Read a :- Read (Identity a)
ins = (Read a => Dict (Read (Identity a))) -> Read a :- Read (Identity a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Read a => Dict (Read (Identity a))
forall (a :: Constraint). a => Dict a
Dict
#if MIN_VERSION_base(4,8,0)
instance Read a :=> Read (Const a b) where ins :: Read a :- Read (Const a b)
ins = (Read a => Dict (Read (Const a b))) -> Read a :- Read (Const a b)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Read a => Dict (Read (Const a b))
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Read Natural where ins :: (() :: Constraint) :- Read Natural
ins = ((() :: Constraint) => Dict (Read Natural))
-> (() :: Constraint) :- Read Natural
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Read Natural)
forall (a :: Constraint). a => Dict a
Dict
#endif
instance Class () (Enum a) where cls :: Enum a :- (() :: Constraint)
cls = (Enum a => Dict (() :: Constraint)) -> Enum a :- (() :: Constraint)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Enum a => Dict (() :: Constraint)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Enum () where ins :: (() :: Constraint) :- Enum ()
ins = ((() :: Constraint) => Dict (Enum ()))
-> (() :: Constraint) :- Enum ()
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Enum ())
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Enum Bool where ins :: (() :: Constraint) :- Enum Bool
ins = ((() :: Constraint) => Dict (Enum Bool))
-> (() :: Constraint) :- Enum Bool
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Enum Bool)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Enum Ordering where ins :: (() :: Constraint) :- Enum Ordering
ins = ((() :: Constraint) => Dict (Enum Ordering))
-> (() :: Constraint) :- Enum Ordering
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Enum Ordering)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Enum Char where ins :: (() :: Constraint) :- Enum Char
ins = ((() :: Constraint) => Dict (Enum Char))
-> (() :: Constraint) :- Enum Char
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Enum Char)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Enum Int where ins :: (() :: Constraint) :- Enum Int
ins = ((() :: Constraint) => Dict (Enum Int))
-> (() :: Constraint) :- Enum Int
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Enum Int)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Enum Integer where ins :: (() :: Constraint) :- Enum Integer
ins = ((() :: Constraint) => Dict (Enum Integer))
-> (() :: Constraint) :- Enum Integer
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Enum Integer)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Enum Float where ins :: (() :: Constraint) :- Enum Float
ins = ((() :: Constraint) => Dict (Enum Float))
-> (() :: Constraint) :- Enum Float
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Enum Float)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Enum Double where ins :: (() :: Constraint) :- Enum Double
ins = ((() :: Constraint) => Dict (Enum Double))
-> (() :: Constraint) :- Enum Double
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Enum Double)
forall (a :: Constraint). a => Dict a
Dict
instance Integral a :=> Enum (Ratio a) where ins :: Integral a :- Enum (Ratio a)
ins = (Integral a => Dict (Enum (Ratio a)))
-> Integral a :- Enum (Ratio a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Integral a => Dict (Enum (Ratio a))
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Enum Word where ins :: (() :: Constraint) :- Enum Word
ins = ((() :: Constraint) => Dict (Enum Word))
-> (() :: Constraint) :- Enum Word
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Enum Word)
forall (a :: Constraint). a => Dict a
Dict
#if MIN_VERSION_base(4,9,0)
instance Enum a :=> Enum (Identity a) where ins :: Enum a :- Enum (Identity a)
ins = (Enum a => Dict (Enum (Identity a))) -> Enum a :- Enum (Identity a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Enum a => Dict (Enum (Identity a))
forall (a :: Constraint). a => Dict a
Dict
instance Enum a :=> Enum (Const a b) where ins :: Enum a :- Enum (Const a b)
ins = (Enum a => Dict (Enum (Const a b))) -> Enum a :- Enum (Const a b)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Enum a => Dict (Enum (Const a b))
forall (a :: Constraint). a => Dict a
Dict
#endif
#if MIN_VERSION_base(4,8,0)
instance () :=> Enum Natural where ins :: (() :: Constraint) :- Enum Natural
ins = ((() :: Constraint) => Dict (Enum Natural))
-> (() :: Constraint) :- Enum Natural
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Enum Natural)
forall (a :: Constraint). a => Dict a
Dict
#endif
instance Class () (Bounded a) where cls :: Bounded a :- (() :: Constraint)
cls = (Bounded a => Dict (() :: Constraint))
-> Bounded a :- (() :: Constraint)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Bounded a => Dict (() :: Constraint)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Bounded () where ins :: (() :: Constraint) :- Bounded ()
ins = ((() :: Constraint) => Dict (Bounded ()))
-> (() :: Constraint) :- Bounded ()
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Bounded ())
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Bounded Ordering where ins :: (() :: Constraint) :- Bounded Ordering
ins = ((() :: Constraint) => Dict (Bounded Ordering))
-> (() :: Constraint) :- Bounded Ordering
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Bounded Ordering)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Bounded Bool where ins :: (() :: Constraint) :- Bounded Bool
ins = ((() :: Constraint) => Dict (Bounded Bool))
-> (() :: Constraint) :- Bounded Bool
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Bounded Bool)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Bounded Int where ins :: (() :: Constraint) :- Bounded Int
ins = ((() :: Constraint) => Dict (Bounded Int))
-> (() :: Constraint) :- Bounded Int
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Bounded Int)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Bounded Char where ins :: (() :: Constraint) :- Bounded Char
ins = ((() :: Constraint) => Dict (Bounded Char))
-> (() :: Constraint) :- Bounded Char
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Bounded Char)
forall (a :: Constraint). a => Dict a
Dict
instance (Bounded a, Bounded b) :=> Bounded (a,b) where ins :: (Bounded a, Bounded b) :- Bounded (a, b)
ins = ((Bounded a, Bounded b) => Dict (Bounded (a, b)))
-> (Bounded a, Bounded b) :- Bounded (a, b)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (Bounded a, Bounded b) => Dict (Bounded (a, b))
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Bounded Word where ins :: (() :: Constraint) :- Bounded Word
ins = ((() :: Constraint) => Dict (Bounded Word))
-> (() :: Constraint) :- Bounded Word
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Bounded Word)
forall (a :: Constraint). a => Dict a
Dict
#if MIN_VERSION_base(4,9,0)
instance Bounded a :=> Bounded (Identity a) where ins :: Bounded a :- Bounded (Identity a)
ins = (Bounded a => Dict (Bounded (Identity a)))
-> Bounded a :- Bounded (Identity a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Bounded a => Dict (Bounded (Identity a))
forall (a :: Constraint). a => Dict a
Dict
instance Bounded a :=> Bounded (Const a b) where ins :: Bounded a :- Bounded (Const a b)
ins = (Bounded a => Dict (Bounded (Const a b)))
-> Bounded a :- Bounded (Const a b)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Bounded a => Dict (Bounded (Const a b))
forall (a :: Constraint). a => Dict a
Dict
#endif
instance Class () (Num a) where cls :: Num a :- (() :: Constraint)
cls = (Num a => Dict (() :: Constraint)) -> Num a :- (() :: Constraint)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Num a => Dict (() :: Constraint)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Num Int where ins :: (() :: Constraint) :- Num Int
ins = ((() :: Constraint) => Dict (Num Int))
-> (() :: Constraint) :- Num Int
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Num Int)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Num Integer where ins :: (() :: Constraint) :- Num Integer
ins = ((() :: Constraint) => Dict (Num Integer))
-> (() :: Constraint) :- Num Integer
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Num Integer)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Num Float where ins :: (() :: Constraint) :- Num Float
ins = ((() :: Constraint) => Dict (Num Float))
-> (() :: Constraint) :- Num Float
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Num Float)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Num Double where ins :: (() :: Constraint) :- Num Double
ins = ((() :: Constraint) => Dict (Num Double))
-> (() :: Constraint) :- Num Double
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Num Double)
forall (a :: Constraint). a => Dict a
Dict
instance RealFloat a :=> Num (Complex a) where ins :: RealFloat a :- Num (Complex a)
ins = (RealFloat a => Dict (Num (Complex a)))
-> RealFloat a :- Num (Complex a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub RealFloat a => Dict (Num (Complex a))
forall (a :: Constraint). a => Dict a
Dict
instance Integral a :=> Num (Ratio a) where ins :: Integral a :- Num (Ratio a)
ins = (Integral a => Dict (Num (Ratio a))) -> Integral a :- Num (Ratio a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Integral a => Dict (Num (Ratio a))
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Num Word where ins :: (() :: Constraint) :- Num Word
ins = ((() :: Constraint) => Dict (Num Word))
-> (() :: Constraint) :- Num Word
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Num Word)
forall (a :: Constraint). a => Dict a
Dict
#if MIN_VERSION_base(4,9,0)
instance Num a :=> Num (Identity a) where ins :: Num a :- Num (Identity a)
ins = (Num a => Dict (Num (Identity a))) -> Num a :- Num (Identity a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Num a => Dict (Num (Identity a))
forall (a :: Constraint). a => Dict a
Dict
instance Num a :=> Num (Const a b) where ins :: Num a :- Num (Const a b)
ins = (Num a => Dict (Num (Const a b))) -> Num a :- Num (Const a b)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Num a => Dict (Num (Const a b))
forall (a :: Constraint). a => Dict a
Dict
#endif
#if MIN_VERSION_base(4,8,0)
instance () :=> Num Natural where ins :: (() :: Constraint) :- Num Natural
ins = ((() :: Constraint) => Dict (Num Natural))
-> (() :: Constraint) :- Num Natural
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Num Natural)
forall (a :: Constraint). a => Dict a
Dict
#endif
instance Class (Num a, Ord a) (Real a) where cls :: Real a :- (Num a, Ord a)
cls = (Real a => Dict (Num a, Ord a)) -> Real a :- (Num a, Ord a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Real a => Dict (Num a, Ord a)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Real Int where ins :: (() :: Constraint) :- Real Int
ins = ((() :: Constraint) => Dict (Real Int))
-> (() :: Constraint) :- Real Int
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Real Int)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Real Integer where ins :: (() :: Constraint) :- Real Integer
ins = ((() :: Constraint) => Dict (Real Integer))
-> (() :: Constraint) :- Real Integer
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Real Integer)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Real Float where ins :: (() :: Constraint) :- Real Float
ins = ((() :: Constraint) => Dict (Real Float))
-> (() :: Constraint) :- Real Float
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Real Float)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Real Double where ins :: (() :: Constraint) :- Real Double
ins = ((() :: Constraint) => Dict (Real Double))
-> (() :: Constraint) :- Real Double
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Real Double)
forall (a :: Constraint). a => Dict a
Dict
instance Integral a :=> Real (Ratio a) where ins :: Integral a :- Real (Ratio a)
ins = (Integral a => Dict (Real (Ratio a)))
-> Integral a :- Real (Ratio a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Integral a => Dict (Real (Ratio a))
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Real Word where ins :: (() :: Constraint) :- Real Word
ins = ((() :: Constraint) => Dict (Real Word))
-> (() :: Constraint) :- Real Word
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Real Word)
forall (a :: Constraint). a => Dict a
Dict
#if MIN_VERSION_base(4,9,0)
instance Real a :=> Real (Identity a) where ins :: Real a :- Real (Identity a)
ins = (Real a => Dict (Real (Identity a))) -> Real a :- Real (Identity a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Real a => Dict (Real (Identity a))
forall (a :: Constraint). a => Dict a
Dict
instance Real a :=> Real (Const a b) where ins :: Real a :- Real (Const a b)
ins = (Real a => Dict (Real (Const a b))) -> Real a :- Real (Const a b)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Real a => Dict (Real (Const a b))
forall (a :: Constraint). a => Dict a
Dict
#endif
#if MIN_VERSION_base(4,8,0)
instance () :=> Real Natural where ins :: (() :: Constraint) :- Real Natural
ins = ((() :: Constraint) => Dict (Real Natural))
-> (() :: Constraint) :- Real Natural
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Real Natural)
forall (a :: Constraint). a => Dict a
Dict
#endif
instance Class (Real a, Enum a) (Integral a) where cls :: Integral a :- (Real a, Enum a)
cls = (Integral a => Dict (Real a, Enum a))
-> Integral a :- (Real a, Enum a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Integral a => Dict (Real a, Enum a)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Integral Int where ins :: (() :: Constraint) :- Integral Int
ins = ((() :: Constraint) => Dict (Integral Int))
-> (() :: Constraint) :- Integral Int
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Integral Int)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Integral Integer where ins :: (() :: Constraint) :- Integral Integer
ins = ((() :: Constraint) => Dict (Integral Integer))
-> (() :: Constraint) :- Integral Integer
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Integral Integer)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Integral Word where ins :: (() :: Constraint) :- Integral Word
ins = ((() :: Constraint) => Dict (Integral Word))
-> (() :: Constraint) :- Integral Word
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Integral Word)
forall (a :: Constraint). a => Dict a
Dict
#if MIN_VERSION_base(4,9,0)
instance Integral a :=> Integral (Identity a) where ins :: Integral a :- Integral (Identity a)
ins = (Integral a => Dict (Integral (Identity a)))
-> Integral a :- Integral (Identity a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Integral a => Dict (Integral (Identity a))
forall (a :: Constraint). a => Dict a
Dict
instance Integral a :=> Integral (Const a b) where ins :: Integral a :- Integral (Const a b)
ins = (Integral a => Dict (Integral (Const a b)))
-> Integral a :- Integral (Const a b)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Integral a => Dict (Integral (Const a b))
forall (a :: Constraint). a => Dict a
Dict
#endif
#if MIN_VERSION_base(4,8,0)
instance () :=> Integral Natural where ins :: (() :: Constraint) :- Integral Natural
ins = ((() :: Constraint) => Dict (Integral Natural))
-> (() :: Constraint) :- Integral Natural
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Integral Natural)
forall (a :: Constraint). a => Dict a
Dict
#endif
instance Class (Eq a) (Bits a) where cls :: Bits a :- Eq a
cls = (Bits a => Dict (Eq a)) -> Bits a :- Eq a
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Bits a => Dict (Eq a)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Bits Bool where ins :: (() :: Constraint) :- Bits Bool
ins = ((() :: Constraint) => Dict (Bits Bool))
-> (() :: Constraint) :- Bits Bool
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Bits Bool)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Bits Int where ins :: (() :: Constraint) :- Bits Int
ins = ((() :: Constraint) => Dict (Bits Int))
-> (() :: Constraint) :- Bits Int
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Bits Int)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Bits Integer where ins :: (() :: Constraint) :- Bits Integer
ins = ((() :: Constraint) => Dict (Bits Integer))
-> (() :: Constraint) :- Bits Integer
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Bits Integer)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Bits Word where ins :: (() :: Constraint) :- Bits Word
ins = ((() :: Constraint) => Dict (Bits Word))
-> (() :: Constraint) :- Bits Word
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Bits Word)
forall (a :: Constraint). a => Dict a
Dict
#if MIN_VERSION_base(4,9,0)
instance Bits a :=> Bits (Identity a) where ins :: Bits a :- Bits (Identity a)
ins = (Bits a => Dict (Bits (Identity a))) -> Bits a :- Bits (Identity a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Bits a => Dict (Bits (Identity a))
forall (a :: Constraint). a => Dict a
Dict
instance Bits a :=> Bits (Const a b) where ins :: Bits a :- Bits (Const a b)
ins = (Bits a => Dict (Bits (Const a b))) -> Bits a :- Bits (Const a b)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Bits a => Dict (Bits (Const a b))
forall (a :: Constraint). a => Dict a
Dict
#endif
#if MIN_VERSION_base(4,8,0)
instance () :=> Bits Natural where ins :: (() :: Constraint) :- Bits Natural
ins = ((() :: Constraint) => Dict (Bits Natural))
-> (() :: Constraint) :- Bits Natural
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Bits Natural)
forall (a :: Constraint). a => Dict a
Dict
#endif
instance Class (Num a) (Fractional a) where cls :: Fractional a :- Num a
cls = (Fractional a => Dict (Num a)) -> Fractional a :- Num a
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Fractional a => Dict (Num a)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Fractional Float where ins :: (() :: Constraint) :- Fractional Float
ins = ((() :: Constraint) => Dict (Fractional Float))
-> (() :: Constraint) :- Fractional Float
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Fractional Float)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Fractional Double where ins :: (() :: Constraint) :- Fractional Double
ins = ((() :: Constraint) => Dict (Fractional Double))
-> (() :: Constraint) :- Fractional Double
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Fractional Double)
forall (a :: Constraint). a => Dict a
Dict
instance RealFloat a :=> Fractional (Complex a) where ins :: RealFloat a :- Fractional (Complex a)
ins = (RealFloat a => Dict (Fractional (Complex a)))
-> RealFloat a :- Fractional (Complex a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub RealFloat a => Dict (Fractional (Complex a))
forall (a :: Constraint). a => Dict a
Dict
instance Integral a :=> Fractional (Ratio a) where ins :: Integral a :- Fractional (Ratio a)
ins = (Integral a => Dict (Fractional (Ratio a)))
-> Integral a :- Fractional (Ratio a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Integral a => Dict (Fractional (Ratio a))
forall (a :: Constraint). a => Dict a
Dict
#if MIN_VERSION_base(4,9,0)
instance Fractional a :=> Fractional (Identity a) where ins :: Fractional a :- Fractional (Identity a)
ins = (Fractional a => Dict (Fractional (Identity a)))
-> Fractional a :- Fractional (Identity a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Fractional a => Dict (Fractional (Identity a))
forall (a :: Constraint). a => Dict a
Dict
instance Fractional a :=> Fractional (Const a b) where ins :: Fractional a :- Fractional (Const a b)
ins = (Fractional a => Dict (Fractional (Const a b)))
-> Fractional a :- Fractional (Const a b)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Fractional a => Dict (Fractional (Const a b))
forall (a :: Constraint). a => Dict a
Dict
#endif
instance Class (Fractional a) (Floating a) where cls :: Floating a :- Fractional a
cls = (Floating a => Dict (Fractional a)) -> Floating a :- Fractional a
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Floating a => Dict (Fractional a)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Floating Float where ins :: (() :: Constraint) :- Floating Float
ins = ((() :: Constraint) => Dict (Floating Float))
-> (() :: Constraint) :- Floating Float
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Floating Float)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Floating Double where ins :: (() :: Constraint) :- Floating Double
ins = ((() :: Constraint) => Dict (Floating Double))
-> (() :: Constraint) :- Floating Double
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Floating Double)
forall (a :: Constraint). a => Dict a
Dict
instance RealFloat a :=> Floating (Complex a) where ins :: RealFloat a :- Floating (Complex a)
ins = (RealFloat a => Dict (Floating (Complex a)))
-> RealFloat a :- Floating (Complex a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub RealFloat a => Dict (Floating (Complex a))
forall (a :: Constraint). a => Dict a
Dict
#if MIN_VERSION_base(4,9,0)
instance Floating a :=> Floating (Identity a) where ins :: Floating a :- Floating (Identity a)
ins = (Floating a => Dict (Floating (Identity a)))
-> Floating a :- Floating (Identity a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Floating a => Dict (Floating (Identity a))
forall (a :: Constraint). a => Dict a
Dict
instance Floating a :=> Floating (Const a b) where ins :: Floating a :- Floating (Const a b)
ins = (Floating a => Dict (Floating (Const a b)))
-> Floating a :- Floating (Const a b)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Floating a => Dict (Floating (Const a b))
forall (a :: Constraint). a => Dict a
Dict
#endif
instance Class (Real a, Fractional a) (RealFrac a) where cls :: RealFrac a :- (Real a, Fractional a)
cls = (RealFrac a => Dict (Real a, Fractional a))
-> RealFrac a :- (Real a, Fractional a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub RealFrac a => Dict (Real a, Fractional a)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> RealFrac Float where ins :: (() :: Constraint) :- RealFrac Float
ins = ((() :: Constraint) => Dict (RealFrac Float))
-> (() :: Constraint) :- RealFrac Float
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (RealFrac Float)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> RealFrac Double where ins :: (() :: Constraint) :- RealFrac Double
ins = ((() :: Constraint) => Dict (RealFrac Double))
-> (() :: Constraint) :- RealFrac Double
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (RealFrac Double)
forall (a :: Constraint). a => Dict a
Dict
instance Integral a :=> RealFrac (Ratio a) where ins :: Integral a :- RealFrac (Ratio a)
ins = (Integral a => Dict (RealFrac (Ratio a)))
-> Integral a :- RealFrac (Ratio a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Integral a => Dict (RealFrac (Ratio a))
forall (a :: Constraint). a => Dict a
Dict
#if MIN_VERSION_base(4,9,0)
instance RealFrac a :=> RealFrac (Identity a) where ins :: RealFrac a :- RealFrac (Identity a)
ins = (RealFrac a => Dict (RealFrac (Identity a)))
-> RealFrac a :- RealFrac (Identity a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub RealFrac a => Dict (RealFrac (Identity a))
forall (a :: Constraint). a => Dict a
Dict
instance RealFrac a :=> RealFrac (Const a b) where ins :: RealFrac a :- RealFrac (Const a b)
ins = (RealFrac a => Dict (RealFrac (Const a b)))
-> RealFrac a :- RealFrac (Const a b)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub RealFrac a => Dict (RealFrac (Const a b))
forall (a :: Constraint). a => Dict a
Dict
#endif
instance Class (RealFrac a, Floating a) (RealFloat a) where cls :: RealFloat a :- (RealFrac a, Floating a)
cls = (RealFloat a => Dict (RealFrac a, Floating a))
-> RealFloat a :- (RealFrac a, Floating a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub RealFloat a => Dict (RealFrac a, Floating a)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> RealFloat Float where ins :: (() :: Constraint) :- RealFloat Float
ins = ((() :: Constraint) => Dict (RealFloat Float))
-> (() :: Constraint) :- RealFloat Float
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (RealFloat Float)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> RealFloat Double where ins :: (() :: Constraint) :- RealFloat Double
ins = ((() :: Constraint) => Dict (RealFloat Double))
-> (() :: Constraint) :- RealFloat Double
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (RealFloat Double)
forall (a :: Constraint). a => Dict a
Dict
#if MIN_VERSION_base(4,9,0)
instance RealFloat a :=> RealFloat (Identity a) where ins :: RealFloat a :- RealFloat (Identity a)
ins = (RealFloat a => Dict (RealFloat (Identity a)))
-> RealFloat a :- RealFloat (Identity a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub RealFloat a => Dict (RealFloat (Identity a))
forall (a :: Constraint). a => Dict a
Dict
instance RealFloat a :=> RealFloat (Const a b) where ins :: RealFloat a :- RealFloat (Const a b)
ins = (RealFloat a => Dict (RealFloat (Const a b)))
-> RealFloat a :- RealFloat (Const a b)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub RealFloat a => Dict (RealFloat (Const a b))
forall (a :: Constraint). a => Dict a
Dict
#endif
instance Class () (Semigroup a) where cls :: Semigroup a :- (() :: Constraint)
cls = (Semigroup a => Dict (() :: Constraint))
-> Semigroup a :- (() :: Constraint)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Semigroup a => Dict (() :: Constraint)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Semigroup () where ins :: (() :: Constraint) :- Semigroup ()
ins = ((() :: Constraint) => Dict (Semigroup ()))
-> (() :: Constraint) :- Semigroup ()
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Semigroup ())
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Semigroup Ordering where ins :: (() :: Constraint) :- Semigroup Ordering
ins = ((() :: Constraint) => Dict (Semigroup Ordering))
-> (() :: Constraint) :- Semigroup Ordering
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Semigroup Ordering)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Semigroup [a] where ins :: (() :: Constraint) :- Semigroup [a]
ins = ((() :: Constraint) => Dict (Semigroup [a]))
-> (() :: Constraint) :- Semigroup [a]
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Semigroup [a])
forall (a :: Constraint). a => Dict a
Dict
instance Semigroup a :=> Semigroup (Maybe a) where ins :: Semigroup a :- Semigroup (Maybe a)
ins = (Semigroup a => Dict (Semigroup (Maybe a)))
-> Semigroup a :- Semigroup (Maybe a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Semigroup a => Dict (Semigroup (Maybe a))
forall (a :: Constraint). a => Dict a
Dict
instance (Semigroup a, Semigroup b) :=> Semigroup (a, b) where ins :: (Semigroup a, Semigroup b) :- Semigroup (a, b)
ins = ((Semigroup a, Semigroup b) => Dict (Semigroup (a, b)))
-> (Semigroup a, Semigroup b) :- Semigroup (a, b)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (Semigroup a, Semigroup b) => Dict (Semigroup (a, b))
forall (a :: Constraint). a => Dict a
Dict
instance Semigroup a :=> Semigroup (Const a b) where ins :: Semigroup a :- Semigroup (Const a b)
ins = (Semigroup a => Dict (Semigroup (Const a b)))
-> Semigroup a :- Semigroup (Const a b)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Semigroup a => Dict (Semigroup (Const a b))
forall (a :: Constraint). a => Dict a
Dict
#if MIN_VERSION_base(4,9,0)
instance Semigroup a :=> Semigroup (Identity a) where ins :: Semigroup a :- Semigroup (Identity a)
ins = (Semigroup a => Dict (Semigroup (Identity a)))
-> Semigroup a :- Semigroup (Identity a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Semigroup a => Dict (Semigroup (Identity a))
forall (a :: Constraint). a => Dict a
Dict
#endif
#if MIN_VERSION_base(4,10,0)
instance Semigroup a :=> Semigroup (IO a) where ins :: Semigroup a :- Semigroup (IO a)
ins = (Semigroup a => Dict (Semigroup (IO a)))
-> Semigroup a :- Semigroup (IO a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Semigroup a => Dict (Semigroup (IO a))
forall (a :: Constraint). a => Dict a
Dict
#endif
#if MIN_VERSION_base(4,11,0)
instance Class (Semigroup a) (Monoid a) where cls :: Monoid a :- Semigroup a
cls = (Monoid a => Dict (Semigroup a)) -> Monoid a :- Semigroup a
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Monoid a => Dict (Semigroup a)
forall (a :: Constraint). a => Dict a
Dict
#else
instance Class () (Monoid a) where cls = Sub Dict
#endif
instance () :=> Monoid () where ins :: (() :: Constraint) :- Monoid ()
ins = ((() :: Constraint) => Dict (Monoid ()))
-> (() :: Constraint) :- Monoid ()
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Monoid ())
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Monoid Ordering where ins :: (() :: Constraint) :- Monoid Ordering
ins = ((() :: Constraint) => Dict (Monoid Ordering))
-> (() :: Constraint) :- Monoid Ordering
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Monoid Ordering)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Monoid [a] where ins :: (() :: Constraint) :- Monoid [a]
ins = ((() :: Constraint) => Dict (Monoid [a]))
-> (() :: Constraint) :- Monoid [a]
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Monoid [a])
forall (a :: Constraint). a => Dict a
Dict
instance Monoid a :=> Monoid (Maybe a) where ins :: Monoid a :- Monoid (Maybe a)
ins = (Monoid a => Dict (Monoid (Maybe a)))
-> Monoid a :- Monoid (Maybe a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Monoid a => Dict (Monoid (Maybe a))
forall (a :: Constraint). a => Dict a
Dict
instance (Monoid a, Monoid b) :=> Monoid (a, b) where ins :: (Monoid a, Monoid b) :- Monoid (a, b)
ins = ((Monoid a, Monoid b) => Dict (Monoid (a, b)))
-> (Monoid a, Monoid b) :- Monoid (a, b)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (Monoid a, Monoid b) => Dict (Monoid (a, b))
forall (a :: Constraint). a => Dict a
Dict
instance Monoid a :=> Monoid (Const a b) where ins :: Monoid a :- Monoid (Const a b)
ins = (Monoid a => Dict (Monoid (Const a b)))
-> Monoid a :- Monoid (Const a b)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Monoid a => Dict (Monoid (Const a b))
forall (a :: Constraint). a => Dict a
Dict
#if MIN_VERSION_base(4,9,0)
instance Monoid a :=> Monoid (Identity a) where ins :: Monoid a :- Monoid (Identity a)
ins = (Monoid a => Dict (Monoid (Identity a)))
-> Monoid a :- Monoid (Identity a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Monoid a => Dict (Monoid (Identity a))
forall (a :: Constraint). a => Dict a
Dict
instance Monoid a :=> Monoid (IO a) where ins :: Monoid a :- Monoid (IO a)
ins = (Monoid a => Dict (Monoid (IO a))) -> Monoid a :- Monoid (IO a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Monoid a => Dict (Monoid (IO a))
forall (a :: Constraint). a => Dict a
Dict
#endif
instance Class () (Functor f) where cls :: Functor f :- (() :: Constraint)
cls = (Functor f => Dict (() :: Constraint))
-> Functor f :- (() :: Constraint)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Functor f => Dict (() :: Constraint)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Functor [] where ins :: (() :: Constraint) :- Functor []
ins = ((() :: Constraint) => Dict (Functor []))
-> (() :: Constraint) :- Functor []
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Functor [])
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Functor Maybe where ins :: (() :: Constraint) :- Functor Maybe
ins = ((() :: Constraint) => Dict (Functor Maybe))
-> (() :: Constraint) :- Functor Maybe
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Functor Maybe)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Functor (Either a) where ins :: (() :: Constraint) :- Functor (Either a)
ins = ((() :: Constraint) => Dict (Functor (Either a)))
-> (() :: Constraint) :- Functor (Either a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Functor (Either a))
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Functor ((->) a) where ins :: (() :: Constraint) :- Functor ((->) a)
ins = ((() :: Constraint) => Dict (Functor ((->) a)))
-> (() :: Constraint) :- Functor ((->) a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Functor ((->) a))
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Functor ((,) a) where ins :: (() :: Constraint) :- Functor ((,) a)
ins = ((() :: Constraint) => Dict (Functor ((,) a)))
-> (() :: Constraint) :- Functor ((,) a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Functor ((,) a))
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Functor IO where ins :: (() :: Constraint) :- Functor IO
ins = ((() :: Constraint) => Dict (Functor IO))
-> (() :: Constraint) :- Functor IO
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Functor IO)
forall (a :: Constraint). a => Dict a
Dict
instance Monad m :=> Functor (WrappedMonad m) where ins :: Monad m :- Functor (WrappedMonad m)
ins = (Monad m => Dict (Functor (WrappedMonad m)))
-> Monad m :- Functor (WrappedMonad m)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Monad m => Dict (Functor (WrappedMonad m))
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Functor Identity where ins :: (() :: Constraint) :- Functor Identity
ins = ((() :: Constraint) => Dict (Functor Identity))
-> (() :: Constraint) :- Functor Identity
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Functor Identity)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Functor (Const a) where ins :: (() :: Constraint) :- Functor (Const a)
ins = ((() :: Constraint) => Dict (Functor (Const a)))
-> (() :: Constraint) :- Functor (Const a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Functor (Const a))
forall (a :: Constraint). a => Dict a
Dict
instance Class (Functor f) (Applicative f) where cls :: Applicative f :- Functor f
cls = (Applicative f => Dict (Functor f)) -> Applicative f :- Functor f
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Applicative f => Dict (Functor f)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Applicative [] where ins :: (() :: Constraint) :- Applicative []
ins = ((() :: Constraint) => Dict (Applicative []))
-> (() :: Constraint) :- Applicative []
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Applicative [])
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Applicative Maybe where ins :: (() :: Constraint) :- Applicative Maybe
ins = ((() :: Constraint) => Dict (Applicative Maybe))
-> (() :: Constraint) :- Applicative Maybe
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Applicative Maybe)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Applicative (Either a) where ins :: (() :: Constraint) :- Applicative (Either a)
ins = ((() :: Constraint) => Dict (Applicative (Either a)))
-> (() :: Constraint) :- Applicative (Either a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Applicative (Either a))
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Applicative ((->)a) where ins :: (() :: Constraint) :- Applicative ((->) a)
ins = ((() :: Constraint) => Dict (Applicative ((->) a)))
-> (() :: Constraint) :- Applicative ((->) a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Applicative ((->) a))
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Applicative IO where ins :: (() :: Constraint) :- Applicative IO
ins = ((() :: Constraint) => Dict (Applicative IO))
-> (() :: Constraint) :- Applicative IO
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Applicative IO)
forall (a :: Constraint). a => Dict a
Dict
instance Monoid a :=> Applicative ((,)a) where ins :: Monoid a :- Applicative ((,) a)
ins = (Monoid a => Dict (Applicative ((,) a)))
-> Monoid a :- Applicative ((,) a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Monoid a => Dict (Applicative ((,) a))
forall (a :: Constraint). a => Dict a
Dict
instance Monoid a :=> Applicative (Const a) where ins :: Monoid a :- Applicative (Const a)
ins = (Monoid a => Dict (Applicative (Const a)))
-> Monoid a :- Applicative (Const a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Monoid a => Dict (Applicative (Const a))
forall (a :: Constraint). a => Dict a
Dict
instance Monad m :=> Applicative (WrappedMonad m) where ins :: Monad m :- Applicative (WrappedMonad m)
ins = (Monad m => Dict (Applicative (WrappedMonad m)))
-> Monad m :- Applicative (WrappedMonad m)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Monad m => Dict (Applicative (WrappedMonad m))
forall (a :: Constraint). a => Dict a
Dict
instance Class (Applicative f) (Alternative f) where cls :: Alternative f :- Applicative f
cls = (Alternative f => Dict (Applicative f))
-> Alternative f :- Applicative f
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Alternative f => Dict (Applicative f)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Alternative [] where ins :: (() :: Constraint) :- Alternative []
ins = ((() :: Constraint) => Dict (Alternative []))
-> (() :: Constraint) :- Alternative []
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Alternative [])
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Alternative Maybe where ins :: (() :: Constraint) :- Alternative Maybe
ins = ((() :: Constraint) => Dict (Alternative Maybe))
-> (() :: Constraint) :- Alternative Maybe
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Alternative Maybe)
forall (a :: Constraint). a => Dict a
Dict
instance MonadPlus m :=> Alternative (WrappedMonad m) where ins :: MonadPlus m :- Alternative (WrappedMonad m)
ins = (MonadPlus m => Dict (Alternative (WrappedMonad m)))
-> MonadPlus m :- Alternative (WrappedMonad m)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub MonadPlus m => Dict (Alternative (WrappedMonad m))
forall (a :: Constraint). a => Dict a
Dict
#if MIN_VERSION_base(4,8,0)
instance Class (Applicative f) (Monad f) where cls :: Monad f :- Applicative f
cls = (Monad f => Dict (Applicative f)) -> Monad f :- Applicative f
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub Monad f => Dict (Applicative f)
forall (a :: Constraint). a => Dict a
Dict
#else
instance Class () (Monad f) where cls = Sub Dict
#endif
instance () :=> Monad [] where ins :: (() :: Constraint) :- Monad []
ins = ((() :: Constraint) => Dict (Monad []))
-> (() :: Constraint) :- Monad []
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Monad [])
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Monad ((->) a) where ins :: (() :: Constraint) :- Monad ((->) a)
ins = ((() :: Constraint) => Dict (Monad ((->) a)))
-> (() :: Constraint) :- Monad ((->) a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Monad ((->) a))
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Monad (Either a) where ins :: (() :: Constraint) :- Monad (Either a)
ins = ((() :: Constraint) => Dict (Monad (Either a)))
-> (() :: Constraint) :- Monad (Either a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Monad (Either a))
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Monad IO where ins :: (() :: Constraint) :- Monad IO
ins = ((() :: Constraint) => Dict (Monad IO))
-> (() :: Constraint) :- Monad IO
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Monad IO)
forall (a :: Constraint). a => Dict a
Dict
instance () :=> Monad Identity where ins :: (() :: Constraint) :- Monad Identity
ins = ((() :: Constraint) => Dict (Monad Identity))
-> (() :: Constraint) :- Monad Identity
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Monad Identity)
forall (a :: Constraint). a => Dict a
Dict
#if MIN_VERSION_base(4,8,0)
instance Class (Monad f, Alternative f) (MonadPlus f) where cls :: MonadPlus f :- (Monad f, Alternative f)
cls = (MonadPlus f => Dict (Monad f, Alternative f))
-> MonadPlus f :- (Monad f, Alternative f)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub MonadPlus f => Dict (Monad f, Alternative f)
forall (a :: Constraint). a => Dict a
Dict
#else
instance Class (Monad f) (MonadPlus f) where cls = Sub Dict
#endif
instance () :=> MonadPlus [] where ins :: (() :: Constraint) :- MonadPlus []
ins = ((() :: Constraint) => Dict (MonadPlus []))
-> (() :: Constraint) :- MonadPlus []
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (MonadPlus [])
forall (a :: Constraint). a => Dict a
Dict
instance () :=> MonadPlus Maybe where ins :: (() :: Constraint) :- MonadPlus Maybe
ins = ((() :: Constraint) => Dict (MonadPlus Maybe))
-> (() :: Constraint) :- MonadPlus Maybe
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (MonadPlus Maybe)
forall (a :: Constraint). a => Dict a
Dict
instance a :=> Enum (Dict a) where ins :: a :- Enum (Dict a)
ins = (a => Dict (Enum (Dict a))) -> a :- Enum (Dict a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub a => Dict (Enum (Dict a))
forall (a :: Constraint). a => Dict a
Dict
instance a => Enum (Dict a) where
toEnum :: Int -> Dict a
toEnum Int
_ = Dict a
forall (a :: Constraint). a => Dict a
Dict
fromEnum :: Dict a -> Int
fromEnum Dict a
Dict = Int
0
instance a :=> Bounded (Dict a) where ins :: a :- Bounded (Dict a)
ins = (a => Dict (Bounded (Dict a))) -> a :- Bounded (Dict a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub a => Dict (Bounded (Dict a))
forall (a :: Constraint). a => Dict a
Dict
instance a => Bounded (Dict a) where
minBound :: Dict a
minBound = Dict a
forall (a :: Constraint). a => Dict a
Dict
maxBound :: Dict a
maxBound = Dict a
forall (a :: Constraint). a => Dict a
Dict
instance a :=> Read (Dict a) where ins :: a :- Read (Dict a)
ins = (a => Dict (Read (Dict a))) -> a :- Read (Dict a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub a => Dict (Read (Dict a))
forall (a :: Constraint). a => Dict a
Dict
deriving instance a => Read (Dict a)
instance () :=> Semigroup (Dict a) where ins :: (() :: Constraint) :- Semigroup (Dict a)
ins = ((() :: Constraint) => Dict (Semigroup (Dict a)))
-> (() :: Constraint) :- Semigroup (Dict a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub (() :: Constraint) => Dict (Semigroup (Dict a))
forall (a :: Constraint). a => Dict a
Dict
instance Semigroup (Dict a) where
Dict a
Dict <> :: Dict a -> Dict a -> Dict a
<> Dict a
Dict = Dict a
forall (a :: Constraint). a => Dict a
Dict
instance a :=> Monoid (Dict a) where ins :: a :- Monoid (Dict a)
ins = (a => Dict (Monoid (Dict a))) -> a :- Monoid (Dict a)
forall (a :: Constraint) (b :: Constraint). (a => Dict b) -> a :- b
Sub a => Dict (Monoid (Dict a))
forall (a :: Constraint). a => Dict a
Dict
instance a => Monoid (Dict a) where
#if !(MIN_VERSION_base(4,11,0))
mappend = (<>)
#endif
mempty :: Dict a
mempty = Dict a
forall (a :: Constraint). a => Dict a
Dict