equational-reasoning-0.4.1.1: Proof assistant for Haskell using DataKinds & PolyKinds

Safe HaskellNone
LanguageHaskell98

Proof.Propositional

Contents

Description

Provides type synonyms for logical connectives.

Synopsis

Documentation

type (/\) a b = (a, b) infixr 3 Source #

type (\/) a b = Either a b infixr 2 Source #

type Not a = a -> Void Source #

exfalso :: a -> Not a -> b Source #

orIntroL :: a -> a \/ b Source #

orIntroR :: b -> a \/ b Source #

orElim :: (a \/ b) -> (a -> c) -> (b -> c) -> c Source #

andIntro :: a -> b -> a /\ b Source #

andElimL :: (a /\ b) -> a Source #

andElimR :: (a /\ b) -> b Source #

orAssocL :: (a \/ (b \/ c)) -> (a \/ b) \/ c Source #

orAssocR :: ((a \/ b) \/ c) -> a \/ (b \/ c) Source #

andAssocL :: (a /\ (b /\ c)) -> (a /\ b) /\ c Source #

andAssocR :: ((a /\ b) /\ c) -> a /\ (b /\ c) Source #

data IsTrue b where Source #

Utility type to convert type-level (Bool-valued) predicate function into concrete witness data-type.

Constructors

Witness :: IsTrue True 

Instances

Eq (IsTrue b) Source # 

Methods

(==) :: IsTrue b -> IsTrue b -> Bool #

(/=) :: IsTrue b -> IsTrue b -> Bool #

Data (IsTrue True) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IsTrue True -> c (IsTrue True) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IsTrue True) #

toConstr :: IsTrue True -> Constr #

dataTypeOf :: IsTrue True -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (IsTrue True)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IsTrue True)) #

gmapT :: (forall b. Data b => b -> b) -> IsTrue True -> IsTrue True #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IsTrue True -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IsTrue True -> r #

gmapQ :: (forall d. Data d => d -> u) -> IsTrue True -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IsTrue True -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IsTrue True -> m (IsTrue True) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IsTrue True -> m (IsTrue True) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IsTrue True -> m (IsTrue True) #

Ord (IsTrue b) Source # 

Methods

compare :: IsTrue b -> IsTrue b -> Ordering #

(<) :: IsTrue b -> IsTrue b -> Bool #

(<=) :: IsTrue b -> IsTrue b -> Bool #

(>) :: IsTrue b -> IsTrue b -> Bool #

(>=) :: IsTrue b -> IsTrue b -> Bool #

max :: IsTrue b -> IsTrue b -> IsTrue b #

min :: IsTrue b -> IsTrue b -> IsTrue b #

Read (IsTrue True) Source # 
Show (IsTrue b) Source # 

Methods

showsPrec :: Int -> IsTrue b -> ShowS #

show :: IsTrue b -> String #

showList :: [IsTrue b] -> ShowS #

Inhabited (IsTrue True) Source # 
Empty (IsTrue False) Source # 

Methods

eliminate :: IsTrue False -> x Source #

withWitness :: IsTrue b -> (b ~ True => r) -> r Source #

class Empty a where Source #

Type-class for types without inhabitants, dual to Inhabited. Current GHC doesn't provide selective-instance, hence we don't Empty provide instances for product types in a generic deriving (DeriveAnyClass).

To derive an instance for each concrete types, use refute.

Since 0.4.0.0.

Methods

eliminate :: a -> x Source #

eliminate :: (Generic a, GEmpty (Rep a)) => a -> x Source #

Instances

Empty Void Source # 

Methods

eliminate :: Void -> x Source #

Empty (IsTrue False) Source # 

Methods

eliminate :: IsTrue False -> x Source #

(Empty a, Empty b) => Empty (Either a b) Source # 

Methods

eliminate :: Either a b -> x Source #

withEmpty :: forall a b. (a -> Void) -> (Empty a => b) -> b Source #

Giving falsity witness by proving Void from 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 Empty instance for concrete (variable-free) types which may contain products.

class Inhabited a where Source #

Types with at least one inhabitant, dual to Empty. | Current GHC doesn't provide selective-instance, hence we don't Empty provide instances for sum types in a generic deriving (DeriveAnyClass).

To derive an instance for each concrete types, use prove.

Since 0.4.0.0.

Methods

trivial :: a Source #

trivial :: (Generic a, GInhabited (Rep a)) => a Source #

Instances

Inhabited () Source # 

Methods

trivial :: () Source #

Inhabited (IsTrue True) Source # 
Inhabited b => Inhabited (a -> b) Source # 

Methods

trivial :: a -> b Source #

(Inhabited a, Inhabited b) => Inhabited (a, b) Source # 

Methods

trivial :: (a, b) Source #

(Inhabited a, Inhabited b, Inhabited c) => Inhabited (a, b, c) Source # 

Methods

trivial :: (a, b, c) Source #

(Inhabited a, Inhabited b, Inhabited c, Inhabited d) => Inhabited (a, b, c, d) Source # 

Methods

trivial :: (a, b, c, d) Source #

withInhabited :: forall a b. a -> (Inhabited a => b) -> b Source #

prove :: TypeQ -> DecsQ Source #

Macro to automatically derive Inhabited instance for concrete (variable-free) types which may contain sums.

Orphan instances

Inhabited Bool Source # 

Methods

trivial :: Bool Source #

Inhabited Char Source # 

Methods

trivial :: Char Source #

Inhabited Double Source # 
Inhabited Float Source # 

Methods

trivial :: Float Source #

Inhabited Int Source # 

Methods

trivial :: Int Source #

Inhabited Integer Source # 
Inhabited Ordering Source # 
Inhabited Word Source # 

Methods

trivial :: Word Source #

Inhabited [a0] Source # 

Methods

trivial :: [a0] Source #

Inhabited (Maybe a0) Source # 

Methods

trivial :: Maybe a0 Source #

Inhabited (Ratio Integer) Source # 
(Inhabited a, Empty b) => Empty (a -> b) Source # 

Methods

eliminate :: (a -> b) -> x Source #

Inhabited ((:~:) k n0 n0) Source # 

Methods

trivial :: (k :~: n0) n0 Source #

Empty ((:~:) Bool False True) Source # 

Methods

eliminate :: (Bool :~: False) True -> x Source #

Empty ((:~:) Bool True False) Source # 

Methods

eliminate :: (Bool :~: True) False -> x Source #

Empty ((:~:) Ordering LT EQ) Source # 

Methods

eliminate :: (Ordering :~: LT) EQ -> x Source #

Empty ((:~:) Ordering LT GT) Source # 

Methods

eliminate :: (Ordering :~: LT) GT -> x Source #

Empty ((:~:) Ordering EQ LT) Source # 

Methods

eliminate :: (Ordering :~: EQ) LT -> x Source #

Empty ((:~:) Ordering EQ GT) Source # 

Methods

eliminate :: (Ordering :~: EQ) GT -> x Source #

Empty ((:~:) Ordering GT LT) Source # 

Methods

eliminate :: (Ordering :~: GT) LT -> x Source #

Empty ((:~:) Ordering GT EQ) Source # 

Methods

eliminate :: (Ordering :~: GT) EQ -> x Source #

Empty ((:~:) * () Int) Source # 

Methods

eliminate :: (* :~: ()) Int -> x Source #

Empty ((:~:) Nat 0 1) Source # 

Methods

eliminate :: (Nat :~: 0) 1 -> x Source #