exinst-base-0.9: @exinst@ support for @base@ package.
Safe HaskellNone
LanguageHaskell2010

Exinst.Base

Description

This module exports Show, Read, Eq, Ord and Generic instances for Some1, Some2, Some3 and Some4 from Exinst, provided situable Dict1, Dict2, Dict3 and Dict4 instances are available.

See the README file for more general documentation: https://hackage.haskell.org/package/exinst#readme

Orphan instances

(c 'False, c 'True) => Dict0 (c :: Bool -> Constraint) Source # 
Instance details

Methods

dict0 :: forall (a0 :: k0). Sing a0 -> Dict (c a0) #

(c (f 'False), c (f 'True)) => Dict1 (c :: k0 -> Constraint) (f :: Bool -> k0) Source # 
Instance details

Methods

dict1 :: forall (a1 :: k1). Sing a1 -> Dict (c (f a1)) #

(Dict1 c (f 'False), Dict1 c (f 'True)) => Dict2 (c :: k0 -> Constraint) (f :: Bool -> k1 -> k0) Source # 
Instance details

Methods

dict2 :: forall (a2 :: k2) (a1 :: k10). Sing a2 -> Sing a1 -> Dict (c (f a2 a1)) #

(Dict2 c (f 'False), Dict2 c (f 'True)) => Dict3 (c :: k0 -> Constraint) (f :: Bool -> k2 -> k1 -> k0) Source # 
Instance details

Methods

dict3 :: forall (a3 :: k3) (a2 :: k20) (a1 :: k10). Sing a3 -> Sing a2 -> Sing a1 -> Dict (c (f a3 a2 a1)) #

(Dict3 c (f 'False), Dict3 c (f 'True)) => Dict4 (c :: k0 -> Constraint) (f :: Bool -> k3 -> k2 -> k1 -> k0) Source # 
Instance details

Methods

dict4 :: forall (a4 :: k4) (a3 :: k30) (a2 :: k20) (a1 :: k10). Sing a4 -> Sing a3 -> Sing a2 -> Sing a1 -> Dict (c (f a4 a3 a2 a1)) #

(SingKind k1, PEnum (Demote k1), PBounded (Demote k1), Generic (Demote k1), Dict1 Generic f, Dict1 (Inj (Eithers1 f)) f) => Generic (Some1 f) Source # 
Instance details

Associated Types

type Rep (Some1 f) :: Type -> Type #

Methods

from :: Some1 f -> Rep (Some1 f) x #

to :: Rep (Some1 f) x -> Some1 f #

(SingKind k1, Read (Demote k1), Dict1 Read f) => Read (Some1 f) Source # 
Instance details

(SingKind k1, Show (Demote k1), Dict1 Show f) => Show (Some1 f) Source # 
Instance details

Methods

showsPrec :: Int -> Some1 f -> ShowS #

show :: Some1 f -> String #

showList :: [Some1 f] -> ShowS #

(SDecide k1, Dict1 Eq f) => Eq (Some1 f) Source # 
Instance details

Methods

(==) :: Some1 f -> Some1 f -> Bool #

(/=) :: Some1 f -> Some1 f -> Bool #

(SingKind k1, SDecide k1, Ord (Demote k1), Dict1 Ord f, Eq (Some1 f)) => Ord (Some1 f) Source # 
Instance details

Methods

compare :: Some1 f -> Some1 f -> Ordering #

(<) :: Some1 f -> Some1 f -> Bool #

(<=) :: Some1 f -> Some1 f -> Bool #

(>) :: Some1 f -> Some1 f -> Bool #

(>=) :: Some1 f -> Some1 f -> Bool #

max :: Some1 f -> Some1 f -> Some1 f #

min :: Some1 f -> Some1 f -> Some1 f #

(SingKind k2, SingKind k1, PEnum (Demote k2), PEnum (Demote k1), PBounded (Demote k2), PBounded (Demote k1), Generic (Demote k2), Generic (Demote k1), Dict2 Generic f, Dict2 (Inj (Eithers2 f)) f) => Generic (Some2 f) Source # 
Instance details

Associated Types

type Rep (Some2 f) :: Type -> Type #

Methods

from :: Some2 f -> Rep (Some2 f) x #

to :: Rep (Some2 f) x -> Some2 f #

(SingKind k2, SingKind k1, Read (Demote k2), Read (Demote k1), Dict2 Read f) => Read (Some2 f) Source # 
Instance details

(SingKind k2, SingKind k1, Show (Demote k2), Show (Demote k1), Dict2 Show f) => Show (Some2 f) Source # 
Instance details

Methods

showsPrec :: Int -> Some2 f -> ShowS #

show :: Some2 f -> String #

showList :: [Some2 f] -> ShowS #

(SDecide k2, SDecide k1, Dict2 Eq f) => Eq (Some2 f) Source # 
Instance details

Methods

(==) :: Some2 f -> Some2 f -> Bool #

(/=) :: Some2 f -> Some2 f -> Bool #

(SingKind k2, SingKind k1, SDecide k2, SDecide k1, Ord (Demote k2), Ord (Demote k1), Dict2 Ord f, Eq (Some2 f)) => Ord (Some2 f) Source # 
Instance details

Methods

compare :: Some2 f -> Some2 f -> Ordering #

(<) :: Some2 f -> Some2 f -> Bool #

(<=) :: Some2 f -> Some2 f -> Bool #

(>) :: Some2 f -> Some2 f -> Bool #

(>=) :: Some2 f -> Some2 f -> Bool #

max :: Some2 f -> Some2 f -> Some2 f #

min :: Some2 f -> Some2 f -> Some2 f #

(SingKind k3, SingKind k2, SingKind k1, PEnum (Demote k3), PEnum (Demote k2), PEnum (Demote k1), PBounded (Demote k3), PBounded (Demote k2), PBounded (Demote k1), Generic (Demote k3), Generic (Demote k2), Generic (Demote k1), Dict3 Generic f, Dict3 (Inj (Eithers3 f)) f) => Generic (Some3 f) Source # 
Instance details

Associated Types

type Rep (Some3 f) :: Type -> Type #

Methods

from :: Some3 f -> Rep (Some3 f) x #

to :: Rep (Some3 f) x -> Some3 f #

(SingKind k3, SingKind k2, SingKind k1, Read (Demote k3), Read (Demote k2), Read (Demote k1), Dict3 Read f) => Read (Some3 f) Source # 
Instance details

(SingKind k3, SingKind k2, SingKind k1, Show (Demote k3), Show (Demote k2), Show (Demote k1), Dict3 Show f) => Show (Some3 f) Source # 
Instance details

Methods

showsPrec :: Int -> Some3 f -> ShowS #

show :: Some3 f -> String #

showList :: [Some3 f] -> ShowS #

(SDecide k3, SDecide k2, SDecide k1, Dict3 Eq f) => Eq (Some3 f) Source # 
Instance details

Methods

(==) :: Some3 f -> Some3 f -> Bool #

(/=) :: Some3 f -> Some3 f -> Bool #

(SingKind k3, SingKind k2, SingKind k1, SDecide k3, SDecide k2, SDecide k1, Ord (Demote k3), Ord (Demote k2), Ord (Demote k1), Dict3 Ord f, Eq (Some3 f)) => Ord (Some3 f) Source # 
Instance details

Methods

compare :: Some3 f -> Some3 f -> Ordering #

(<) :: Some3 f -> Some3 f -> Bool #

(<=) :: Some3 f -> Some3 f -> Bool #

(>) :: Some3 f -> Some3 f -> Bool #

(>=) :: Some3 f -> Some3 f -> Bool #

max :: Some3 f -> Some3 f -> Some3 f #

min :: Some3 f -> Some3 f -> Some3 f #

(SingKind k4, SingKind k3, SingKind k2, SingKind k1, PEnum (Demote k4), PEnum (Demote k3), PEnum (Demote k2), PEnum (Demote k1), PBounded (Demote k4), PBounded (Demote k3), PBounded (Demote k2), PBounded (Demote k1), Generic (Demote k4), Generic (Demote k3), Generic (Demote k2), Generic (Demote k1), Dict4 Generic f, Dict4 (Inj (Eithers4 f)) f) => Generic (Some4 f) Source # 
Instance details

Associated Types

type Rep (Some4 f) :: Type -> Type #

Methods

from :: Some4 f -> Rep (Some4 f) x #

to :: Rep (Some4 f) x -> Some4 f #

(SingKind k4, SingKind k3, SingKind k2, SingKind k1, Read (Demote k4), Read (Demote k3), Read (Demote k2), Read (Demote k1), Dict4 Read f) => Read (Some4 f) Source # 
Instance details

(SingKind k4, SingKind k3, SingKind k2, SingKind k1, Show (Demote k4), Show (Demote k3), Show (Demote k2), Show (Demote k1), Dict4 Show f) => Show (Some4 f) Source # 
Instance details

Methods

showsPrec :: Int -> Some4 f -> ShowS #

show :: Some4 f -> String #

showList :: [Some4 f] -> ShowS #

(SDecide k4, SDecide k3, SDecide k2, SDecide k1, Dict4 Eq f) => Eq (Some4 f) Source # 
Instance details

Methods

(==) :: Some4 f -> Some4 f -> Bool #

(/=) :: Some4 f -> Some4 f -> Bool #

(SingKind k4, SingKind k3, SingKind k2, SingKind k1, SDecide k4, SDecide k3, SDecide k2, SDecide k1, Ord (Demote k4), Ord (Demote k3), Ord (Demote k2), Ord (Demote k1), Dict4 Ord f, Eq (Some4 f)) => Ord (Some4 f) Source # 
Instance details

Methods

compare :: Some4 f -> Some4 f -> Ordering #

(<) :: Some4 f -> Some4 f -> Bool #

(<=) :: Some4 f -> Some4 f -> Bool #

(>) :: Some4 f -> Some4 f -> Bool #

(>=) :: Some4 f -> Some4 f -> Bool #

max :: Some4 f -> Some4 f -> Some4 f #

min :: Some4 f -> Some4 f -> Some4 f #