Safe Haskell | None |
---|---|
Language | Haskell98 |
Provides type synonyms for logical connectives.
- type (/\) a b = (a, b)
- type (\/) a b = Either a b
- type Not a = a -> Void
- exfalso :: a -> Not a -> b
- orIntroL :: a -> a \/ b
- orIntroR :: b -> a \/ b
- orElim :: (a \/ b) -> (a -> c) -> (b -> c) -> c
- andIntro :: a -> b -> a /\ b
- andElimL :: (a /\ b) -> a
- andElimR :: (a /\ b) -> b
- orAssocL :: (a \/ (b \/ c)) -> (a \/ b) \/ c
- orAssocR :: ((a \/ b) \/ c) -> a \/ (b \/ c)
- andAssocL :: (a /\ (b /\ c)) -> (a /\ b) /\ c
- andAssocR :: ((a /\ b) /\ c) -> a /\ (b /\ c)
- data IsTrue b where
- withWitness :: IsTrue b -> (b ~ True => r) -> r
- class Empty a where
- withEmpty :: forall a b. (a -> Void) -> (Empty a => b) -> b
- withEmpty' :: forall a b. (forall c. a -> c) -> (Empty a => b) -> b
- refute :: TypeQ -> DecsQ
- class Inhabited a where
- withInhabited :: forall a b. a -> (Inhabited a => b) -> b
- prove :: TypeQ -> DecsQ
Documentation
Utility type to convert type-level (
-valued) predicate function
into concrete witness data-type.Bool
withWitness :: IsTrue b -> (b ~ True => r) -> r Source #
withEmpty :: forall a b. (a -> Void) -> (Empty a => b) -> b Source #
Giving falsity witness by proving
from Void
a
.
See also withEmpty'
.
Since 0.4.0.0
withEmpty' :: forall a b. (forall c. a -> c) -> (Empty a => b) -> b Source #
Giving falsity witness by showing a
entails everything.
See also withEmpty
.
Since 0.4.0.0
refute :: TypeQ -> DecsQ Source #
Macro to automatically derive
instance for
concrete (variable-free) types which may contain products.Empty
class Inhabited a where Source #
Types with at least one inhabitant, dual to
.
| Current GHC doesn't provide selective-instance,
hence we don't Empty
provide instances
for sum types in a generic deriving (DeriveAnyClass).Empty
To derive an instance for each concrete types,
use
.prove
Since 0.4.0.0.
Inhabited () Source # | |
Inhabited (IsTrue True) Source # | |
Inhabited b => Inhabited (a -> b) Source # | |
(Inhabited a, Inhabited b) => Inhabited (a, b) Source # | |
(Inhabited a, Inhabited b, Inhabited c) => Inhabited (a, b, c) Source # | |
(Inhabited a, Inhabited b, Inhabited c, Inhabited d) => Inhabited (a, b, c, d) Source # | |
withInhabited :: forall a b. a -> (Inhabited a => b) -> b Source #
prove :: TypeQ -> DecsQ Source #
Macro to automatically derive
instance for
concrete (variable-free) types which may contain sums.Inhabited
Orphan instances
Inhabited Bool Source # | |
Inhabited Char Source # | |
Inhabited Double Source # | |
Inhabited Float Source # | |
Inhabited Int Source # | |
Inhabited Integer Source # | |
Inhabited Ordering Source # | |
Inhabited Word Source # | |
Inhabited [a0] Source # | |
Inhabited (Maybe a0) Source # | |
Inhabited (Ratio Integer) Source # | |
(Inhabited a, Empty b) => Empty (a -> b) Source # | |
Inhabited ((:~:) k n0 n0) Source # | |
Empty ((:~:) Bool False True) Source # | |
Empty ((:~:) Bool True False) Source # | |
Empty ((:~:) Ordering LT EQ) Source # | |
Empty ((:~:) Ordering LT GT) Source # | |
Empty ((:~:) Ordering EQ LT) Source # | |
Empty ((:~:) Ordering EQ GT) Source # | |
Empty ((:~:) Ordering GT LT) Source # | |
Empty ((:~:) Ordering GT EQ) Source # | |
Empty ((:~:) * () Int) Source # | |
Empty ((:~:) Nat 0 1) Source # | |