Copyright | (C) 2013 Richard Eisenberg |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | Richard Eisenberg ([email protected]) |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Data.Singletons.Decide
Description
Defines the class SDecide
, allowing for decidable equality over singletons.
The SDecide class
class SDecide k where Source #
Members of the SDecide
"kind" class support decidable equality. Instances
of this class are generated alongside singleton definitions for datatypes that
derive an Eq
instance.
Minimal complete definition
Supporting definitions
data (a :: k) :~: (b :: k) :: forall k. k -> k -> * where infix 4 #
Propositional equality. If a :~: b
is inhabited by some terminating
value, then the type a
is the same as the type b
. To use this equality
in practice, pattern-match on the a :~: b
to get out the Refl
constructor;
in the body of the pattern-match, the compiler knows that a ~ b
.
Since: 4.7.0.0
Instances
TestCoercion ((:~:) a :: k -> *) | Since: 4.7.0.0 |
TestEquality ((:~:) a :: k -> *) | Since: 4.7.0.0 |
a ~ b => Bounded (a :~: b) | Since: 4.7.0.0 |
a ~ b => Enum (a :~: b) | Since: 4.7.0.0 |
Methods succ :: (a :~: b) -> a :~: b # pred :: (a :~: b) -> a :~: b # fromEnum :: (a :~: b) -> Int # enumFrom :: (a :~: b) -> [a :~: b] # enumFromThen :: (a :~: b) -> (a :~: b) -> [a :~: b] # enumFromTo :: (a :~: b) -> (a :~: b) -> [a :~: b] # enumFromThenTo :: (a :~: b) -> (a :~: b) -> (a :~: b) -> [a :~: b] # | |
Eq (a :~: b) | |
(a ~ b, Data a) => Data (a :~: b) | Since: 4.7.0.0 |
Methods gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> (a :~: b) -> c (a :~: b) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (a :~: b) # toConstr :: (a :~: b) -> Constr # dataTypeOf :: (a :~: b) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (a :~: b)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (a :~: b)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> (a :~: b) -> a :~: b # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (a :~: b) -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (a :~: b) -> r # gmapQ :: (forall d. Data d => d -> u) -> (a :~: b) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> (a :~: b) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> (a :~: b) -> m (a :~: b) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (a :~: b) -> m (a :~: b) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (a :~: b) -> m (a :~: b) # | |
Ord (a :~: b) | |
a ~ b => Read (a :~: b) | Since: 4.7.0.0 |
Show (a :~: b) | |
Uninhabited data type
Since: 4.8.0.0
Instances
Eq Void | Since: 4.8.0.0 |
Data Void | Since: 4.8.0.0 |
Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Void -> c Void # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Void # dataTypeOf :: Void -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Void) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Void) # gmapT :: (forall b. Data b => b -> b) -> Void -> Void # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Void -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Void -> r # gmapQ :: (forall d. Data d => d -> u) -> Void -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Void -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Void -> m Void # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Void -> m Void # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Void -> m Void # | |
Ord Void | Since: 4.8.0.0 |
Read Void | Reading a Since: 4.8.0.0 |
Show Void | Since: 4.8.0.0 |
Ix Void | Since: 4.8.0.0 |
Generic Void | |
Semigroup Void | Since: 4.9.0.0 |
Exception Void | Since: 4.8.0.0 |
Methods toException :: Void -> SomeException # fromException :: SomeException -> Maybe Void # displayException :: Void -> String # | |
PEq Void Source # | |
SEq Void Source # | |
SOrd Void Source # | |
Methods sCompare :: Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source # (%<) :: Sing t -> Sing t -> Sing (Apply (Apply (<@#@$) t) t) Source # (%<=) :: Sing t -> Sing t -> Sing (Apply (Apply (<=@#@$) t) t) Source # (%>) :: Sing t -> Sing t -> Sing (Apply (Apply (>@#@$) t) t) Source # (%>=) :: Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source # sMax :: Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source # sMin :: Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source # | |
POrd Void Source # | |
ShowSing Void Source # | |
SShow Void Source # | |
PShow Void Source # | |
SuppressUnusedWarnings (AbsurdSym0 :: TyFun Void a6989586621679285232 -> *) Source # | |
Methods suppressUnusedWarnings :: () Source # | |
type Rep Void | Since: 4.8.0.0 |
type Demote Void Source # | |
data Sing (z :: Void) Source # | |
type Show_ (arg :: Void) Source # | |
type (a :: Void) == (b :: Void) Source # | |
type (x :: Void) /= (y :: Void) Source # | |
type Compare (a1 :: Void) (a2 :: Void) Source # | |
type (arg1 :: Void) < (arg2 :: Void) Source # | |
type (arg1 :: Void) <= (arg2 :: Void) Source # | |
type (arg1 :: Void) > (arg2 :: Void) Source # | |
type (arg1 :: Void) >= (arg2 :: Void) Source # | |
type Max (arg1 :: Void) (arg2 :: Void) Source # | |
type Min (arg1 :: Void) (arg2 :: Void) Source # | |
type ShowList (arg1 :: [Void]) arg2 Source # | |
type ShowsPrec a1 (a2 :: Void) a3 Source # | |
type Apply (AbsurdSym0 :: TyFun Void k2 -> *) (l :: Void) Source # | |
A Decision
about a type a
is either a proof of existence or a proof that a
cannot exist.