simple-topes-0.1.0.0
Safe HaskellSafe-Inferred
LanguageHaskell2010

RSTT.Tope.Proof

Synopsis

Documentation

>>> :set -XOverloadedStrings
>>> import RSTT.Tope

Tope sequent

data Sequent Source #

Tope sequent \( \Xi \mid \Phi \vdash \psi \).

Constructors

Sequent 

Fields

Instances

Instances details
Show Sequent Source # 
Instance details

Defined in RSTT.Tope.Proof

Eq Sequent Source # 
Instance details

Defined in RSTT.Tope.Proof

Methods

(==) :: Sequent -> Sequent -> Bool #

(/=) :: Sequent -> Sequent -> Bool #

MonadReader Sequent RulesM Source # 
Instance details

Defined in RSTT.Tope.Proof

Methods

ask :: RulesM Sequent #

local :: (Sequent -> Sequent) -> RulesM a -> RulesM a #

reader :: (Sequent -> a) -> RulesM a #

ppSequent :: Sequent -> String Source #

Pretty-print a Sequent.

>>> points = [("t", "I"), ("s", "J")]
>>> topes = [("φ" `TopeOr` "ζ") `TopeAnd` ("ψ" `TopeOr` "χ"), ("t" `TopeEQ` "s")]
>>> putStrLn (ppSequent (Sequent points topes ("s" `TopeEQ` "t")))
t : I, s : J | (φ ∨ ζ) ∧ (ψ ∨ χ), t ≡ s ⊢ s ≡ t

Rules

type RuleName = String Source #

A name of a (tope inference) rule.

type Rules = RulesM (RuleName, [Sequent]) Source #

A collection of tope inference rules. Intuitively, Rules is a non-deterministic function from Sequent to (RuleName, [Sequent]).

newtype RulesM a Source #

A collection of generalized tope inference rules. Intuitively, RulesM a is a non-deterministic function from Sequent to a.

Constructors

RulesM 

Instances

Instances details
MonadFail RulesM Source # 
Instance details

Defined in RSTT.Tope.Proof

Methods

fail :: String -> RulesM a #

Alternative RulesM Source # 
Instance details

Defined in RSTT.Tope.Proof

Methods

empty :: RulesM a #

(<|>) :: RulesM a -> RulesM a -> RulesM a #

some :: RulesM a -> RulesM [a] #

many :: RulesM a -> RulesM [a] #

Applicative RulesM Source # 
Instance details

Defined in RSTT.Tope.Proof

Methods

pure :: a -> RulesM a #

(<*>) :: RulesM (a -> b) -> RulesM a -> RulesM b #

liftA2 :: (a -> b -> c) -> RulesM a -> RulesM b -> RulesM c #

(*>) :: RulesM a -> RulesM b -> RulesM b #

(<*) :: RulesM a -> RulesM b -> RulesM a #

Functor RulesM Source # 
Instance details

Defined in RSTT.Tope.Proof

Methods

fmap :: (a -> b) -> RulesM a -> RulesM b #

(<$) :: a -> RulesM b -> RulesM a #

Monad RulesM Source # 
Instance details

Defined in RSTT.Tope.Proof

Methods

(>>=) :: RulesM a -> (a -> RulesM b) -> RulesM b #

(>>) :: RulesM a -> RulesM b -> RulesM b #

return :: a -> RulesM a #

MonadPlus RulesM Source # 
Instance details

Defined in RSTT.Tope.Proof

Methods

mzero :: RulesM a #

mplus :: RulesM a -> RulesM a -> RulesM a #

MonadLogic RulesM Source # 
Instance details

Defined in RSTT.Tope.Proof

Methods

msplit :: RulesM a -> RulesM (Maybe (a, RulesM a)) #

interleave :: RulesM a -> RulesM a -> RulesM a #

(>>-) :: RulesM a -> (a -> RulesM b) -> RulesM b #

once :: RulesM a -> RulesM a #

lnot :: RulesM a -> RulesM () #

ifte :: RulesM a -> (a -> RulesM b) -> RulesM b -> RulesM b #

MonadReader Sequent RulesM Source # 
Instance details

Defined in RSTT.Tope.Proof

Methods

ask :: RulesM Sequent #

local :: (Sequent -> Sequent) -> RulesM a -> RulesM a #

reader :: (Sequent -> a) -> RulesM a #

Monoid (RulesM a) Source # 
Instance details

Defined in RSTT.Tope.Proof

Methods

mempty :: RulesM a #

mappend :: RulesM a -> RulesM a -> RulesM a #

mconcat :: [RulesM a] -> RulesM a #

Semigroup (RulesM a) Source # 
Instance details

Defined in RSTT.Tope.Proof

Methods

(<>) :: RulesM a -> RulesM a -> RulesM a #

sconcat :: NonEmpty (RulesM a) -> RulesM a #

stimes :: Integral b => b -> RulesM a -> RulesM a #

data DefinedRules Source #

Rules, collected by type.

Constructors

DefinedRules 

Fields

Sets of rules

rulesLJ :: DefinedRules Source #

Rules for intuitionistic tope logic:

rulesEQ :: DefinedRules Source #

Rules for tope equality:

rulesLJE :: DefinedRules Source #

Rules for intuitionistic tope logic with equality:

rulesLEQ :: Rules Source #

Rules for inequality tope (not built-in).

Intuitionistic logic rules (LJ)

Equality tope \((\equiv)\) rules

reflEQ :: Rules Source #

Transitivity rule for equality tope (see TopeEQ).

———————————
 ⋅ ⊢ x ≡ x

transEQ :: Rules Source #

Transitivity rule for equality tope (see TopeEQ).

     x ≡ y, y ≡ z ⊢ φ
—————————————————————————
 x ≡ y, y ≡ z, x ≡ z ⊢ φ

symEQ :: Rules Source #

Symmetry rule for equality tope (see TopeEQ).

    x ≡ y ⊢ φ
——————————————————
 x ≡ y, y ≡ x ⊢ φ

substEQ :: Rules Source #

Substitution rule for equality tope (see TopeEQ).

   Г, x ≡ y ⊢ φ
—————————————————
 Г[yx] ⊢ φ[yx]

NOTE: limited to replacing a variable, not an arbitrary point subterm.

Inequality tope \((\leq)\) rules

Helpers

orElse :: MonadLogic m => m a -> m a -> m a Source #

Try the second computation only if the first one fails (i.e. no backtracking).

The following examples show the difference between orElse and mplus for Logic:

>>> observeAll (pure 1 `orElse` pure 2)
[1]
>>> observeAll (pure 1 `mplus` pure 2)
[1,2]
>>> observeAll $ do { x <- pure 1 `orElse` pure 2; guard (even x); return x }
[]
>>> observeAll $ do { x <- pure 1 `mplus` pure 2; guard (even x); return x }
[2]

selectN :: Alternative f => Int -> [a] -> f ([a], [a]) Source #

Nondeterministically select exactly \(N\) elements from a given list, also returning the remaining part of the list.

selectOne :: (Alternative f, MonadFail f) => [a] -> f (a, [a]) Source #

Nondeterministically select exactly one element from a given list, also returning the remaining part of the list.

choose :: Alternative f => [a] -> f a Source #

Nondeterministically select exactly one element from a given list.

Proof tree

type Proof = ProofTree Void Source #

A complete proof is a proof tree without any unfinished parts.

data ProofTree a Source #

A proof tree parametrized by the type of leaves (unfinished proofs).

Constructors

Leaf a

A leaf represents an unfinished part of a proof.

Node Sequent RuleName [ProofTree a]

A node in a proof tree corresponds to a single rule application.

Instances

Instances details
Foldable ProofTree Source # 
Instance details

Defined in RSTT.Tope.Proof

Methods

fold :: Monoid m => ProofTree m -> m #

foldMap :: Monoid m => (a -> m) -> ProofTree a -> m #

foldMap' :: Monoid m => (a -> m) -> ProofTree a -> m #

foldr :: (a -> b -> b) -> b -> ProofTree a -> b #

foldr' :: (a -> b -> b) -> b -> ProofTree a -> b #

foldl :: (b -> a -> b) -> b -> ProofTree a -> b #

foldl' :: (b -> a -> b) -> b -> ProofTree a -> b #

foldr1 :: (a -> a -> a) -> ProofTree a -> a #

foldl1 :: (a -> a -> a) -> ProofTree a -> a #

toList :: ProofTree a -> [a] #

null :: ProofTree a -> Bool #

length :: ProofTree a -> Int #

elem :: Eq a => a -> ProofTree a -> Bool #

maximum :: Ord a => ProofTree a -> a #

minimum :: Ord a => ProofTree a -> a #

sum :: Num a => ProofTree a -> a #

product :: Num a => ProofTree a -> a #

Traversable ProofTree Source # 
Instance details

Defined in RSTT.Tope.Proof

Methods

traverse :: Applicative f => (a -> f b) -> ProofTree a -> f (ProofTree b) #

sequenceA :: Applicative f => ProofTree (f a) -> f (ProofTree a) #

mapM :: Monad m => (a -> m b) -> ProofTree a -> m (ProofTree b) #

sequence :: Monad m => ProofTree (m a) -> m (ProofTree a) #

Applicative ProofTree Source # 
Instance details

Defined in RSTT.Tope.Proof

Methods

pure :: a -> ProofTree a #

(<*>) :: ProofTree (a -> b) -> ProofTree a -> ProofTree b #

liftA2 :: (a -> b -> c) -> ProofTree a -> ProofTree b -> ProofTree c #

(*>) :: ProofTree a -> ProofTree b -> ProofTree b #

(<*) :: ProofTree a -> ProofTree b -> ProofTree a #

Functor ProofTree Source # 
Instance details

Defined in RSTT.Tope.Proof

Methods

fmap :: (a -> b) -> ProofTree a -> ProofTree b #

(<$) :: a -> ProofTree b -> ProofTree a #

Monad ProofTree Source # 
Instance details

Defined in RSTT.Tope.Proof

Methods

(>>=) :: ProofTree a -> (a -> ProofTree b) -> ProofTree b #

(>>) :: ProofTree a -> ProofTree b -> ProofTree b #

return :: a -> ProofTree a #

Show a => Show (ProofTree a) Source # 
Instance details

Defined in RSTT.Tope.Proof

Eq a => Eq (ProofTree a) Source # 
Instance details

Defined in RSTT.Tope.Proof

Methods

(==) :: ProofTree a -> ProofTree a -> Bool #

(/=) :: ProofTree a -> ProofTree a -> Bool #

close :: Alternative f => ProofTree a -> f Proof Source #

Convert a proof tree into a complete proof if possible.

ASCII rendering

ppProof :: Proof -> String Source #

Pretty print a proof tree (in ASCII form).

proofNodesWithDepth :: Proof -> [(Int, String)] Source #

Extract proof nodes with corresponding depths.

ppNodesWithDepth :: [(Int, String)] -> String Source #

Pretty-print depth-annotated nodes as a ASCII tree-like structure.

>>> putStr $ ppNodesWithDepth (zip [0,1,2,1,2,3,3,2,3] (map show [0..]))
0
├─ 1
│  └─ 2
└─ 3
   ├─ 4
   │  ├─ 5
   │  └─ 6
   └─ 7
      └─ 8

depthsTree :: [Int] -> [String] Source #

Pretty-print an ASCII tree-like structure based on depth list.

>>> mapM_ putStrLn $ depthsTree [0,1,2,1,2,3,3,2,3]
└─
   ├─
   │  └─
   └─
      ├─
      │  ├─
      │  └─
      └─
         └─

Provers

proveWithDFS Source #

Arguments

:: Int

Maximum search depth.

-> Rules

Set of rules.

-> Sequent

Starting sequent (one to prove).

-> Logic (ProofTree Sequent)

A proof tree, possibly with unproven sequents in leaves (for when maximum search depth is insufficient).

A simple DFS proof search algorithm for a given set of rules.

proveWithBFSviaDFS Source #

Arguments

:: Int

Maximum number of limited DFS iterations.

-> Int

Maximum depth per one DFS iteration.

-> Rules

A set of rules.

-> Sequent

A starting sequent (one to prove).

-> Logic Proof 

A simple k-depth proof search algorithm for a given set of rules.

proveWithDFS' Source #

Arguments

:: Int

Maximum search depth.

-> Rules

Set of rules.

-> Sequent

Starting sequent (one to prove).

-> Maybe Proof 

Search for a proof using simple DFS algorithm (see proveWithDFS).

proveWithBFSviaDFS' Source #

Arguments

:: Int

Maximum number of limited DFS iterations.

-> Int

Maximum depth per one DFS iteration.

-> Rules

A set of rules.

-> Sequent

A starting sequent (one to prove).

-> Maybe Proof 

Search for a proof using a combination of BFS and DFS algorithms (see proveWithBFS).

With printers

proveAndPrintBFS Source #

Arguments

:: Int

Maximum search depth.

-> Rules

Set of rules.

-> Sequent

Starting sequent (one to prove).

-> IO () 

Search for a proof using BFS and print proof tree (see ppProof).

proveAndPrintBFSviaDFS :: Int -> Int -> Rules -> Sequent -> IO () Source #

Search for a proof using a combination of BFS and DFS and print proof tree (see ppProof).

proveAndPrintDFS :: Int -> Rules -> Sequent -> IO () Source #

Search for a proof using DFS and print proof tree (see ppProof).

Examples

ex1 :: Sequent Source #

>>> putStrLn (ppSequent ex1)
⋅ | (φ ∨ ζ) ∧ (ψ ∨ χ) ⊢ φ ∧ ψ ∨ ζ ∧ ψ ∨ χ
>>> proveAndPrintBFS 8 (fromDefinedRules rulesLJ) ex1
[∧L]  ⋅ | (φ ∨ ζ) ∧ (ψ ∨ χ) ⊢ φ ∧ ψ ∨ ζ ∧ ψ ∨ χ
└─ [∨L]  ⋅ | φ ∨ ζ, ψ ∨ χ ⊢ φ ∧ ψ ∨ ζ ∧ ψ ∨ χ
   ├─ [∨L]  ⋅ | φ, ψ ∨ χ ⊢ φ ∧ ψ ∨ ζ ∧ ψ ∨ χ
   │  ├─ [∨R₁]  ⋅ | ψ, φ ⊢ φ ∧ ψ ∨ ζ ∧ ψ ∨ χ
   │  │  └─ [∧R]  ⋅ | ψ, φ ⊢ φ ∧ ψ
   │  │     ├─ [Ax]  ⋅ | ψ, φ ⊢ φ
   │  │     └─ [Ax]  ⋅ | ψ, φ ⊢ ψ
   │  └─ [∨R₂]  ⋅ | χ, φ ⊢ φ ∧ ψ ∨ ζ ∧ ψ ∨ χ
   │     └─ [∨R₂]  ⋅ | χ, φ ⊢ ζ ∧ ψ ∨ χ
   │        └─ [Ax]  ⋅ | χ, φ ⊢ χ
   └─ [∨L]  ⋅ | ζ, ψ ∨ χ ⊢ φ ∧ ψ ∨ ζ ∧ ψ ∨ χ
      ├─ [∨R₂]  ⋅ | ψ, ζ ⊢ φ ∧ ψ ∨ ζ ∧ ψ ∨ χ
      │  └─ [∨R₁]  ⋅ | ψ, ζ ⊢ ζ ∧ ψ ∨ χ
      │     └─ [∧R]  ⋅ | ψ, ζ ⊢ ζ ∧ ψ
      │        ├─ [Ax]  ⋅ | ψ, ζ ⊢ ζ
      │        └─ [Ax]  ⋅ | ψ, ζ ⊢ ψ
      └─ [∨R₂]  ⋅ | χ, ζ ⊢ φ ∧ ψ ∨ ζ ∧ ψ ∨ χ
         └─ [∨R₂]  ⋅ | χ, ζ ⊢ ζ ∧ ψ ∨ χ
            └─ [Ax]  ⋅ | χ, ζ ⊢ χ

ex2 :: Sequent Source #

>>> putStrLn (ppSequent ex2)
⋅ | φ ∧ ψ ∨ ζ ∧ χ ⊢ (φ ∨ ζ) ∧ (ψ ∨ χ)
>>> proveAndPrintBFS 8 (fromDefinedRules rulesLJ) ex2
[∧R]  ⋅ | φ ∧ ψ ∨ ζ ∧ χ ⊢ (φ ∨ ζ) ∧ (ψ ∨ χ)
├─ [∨L]  ⋅ | φ ∧ ψ ∨ ζ ∧ χ ⊢ φ ∨ ζ
│  ├─ [∧L]  ⋅ | φ ∧ ψ ⊢ φ ∨ ζ
│  │  └─ [∨R₁]  ⋅ | φ, ψ ⊢ φ ∨ ζ
│  │     └─ [Ax]  ⋅ | φ, ψ ⊢ φ
│  └─ [∧L]  ⋅ | ζ ∧ χ ⊢ φ ∨ ζ
│     └─ [∨R₂]  ⋅ | ζ, χ ⊢ φ ∨ ζ
│        └─ [Ax]  ⋅ | ζ, χ ⊢ ζ
└─ [∨L]  ⋅ | φ ∧ ψ ∨ ζ ∧ χ ⊢ ψ ∨ χ
   ├─ [∧L]  ⋅ | φ ∧ ψ ⊢ ψ ∨ χ
   │  └─ [∨R₁]  ⋅ | φ, ψ ⊢ ψ ∨ χ
   │     └─ [Ax]  ⋅ | φ, ψ ⊢ ψ
   └─ [∧L]  ⋅ | ζ ∧ χ ⊢ ψ ∨ χ
      └─ [∨R₂]  ⋅ | ζ, χ ⊢ ψ ∨ χ
         └─ [Ax]  ⋅ | ζ, χ ⊢ χ

ex3 :: Sequent Source #

>>> putStrLn (ppSequent ex3)
⋅ | x ≡ y ∧ y ≡ z ⊢ z ≡ x
>>> proveAndPrintBFS 35 (fromDefinedRules rulesLJE) ex3
[∧L]  ⋅ | x ≡ y ∧ y ≡ z ⊢ z ≡ x
└─ [≡L(trans)]  ⋅ | x ≡ y, y ≡ z ⊢ z ≡ x
   └─ [≡L(sym)]  ⋅ | x ≡ z, x ≡ y, y ≡ z ⊢ z ≡ x
      └─ [Ax]  ⋅ | z ≡ x, x ≡ z, x ≡ y, y ≡ z ⊢ z ≡ x

ex4 :: Sequent Source #

>>> putStrLn (ppSequent ex4)
⋅ | (t ≡ s ∨ t ≡ u) ∧ s ≡ u ⊢ t ≡ s
>>> proveAndPrintBFS 8 (fromDefinedRules rulesLJE) ex4
[∧L]  ⋅ | (t ≡ s ∨ t ≡ u) ∧ s ≡ u ⊢ t ≡ s
└─ [∨L]  ⋅ | t ≡ s ∨ t ≡ u, s ≡ u ⊢ t ≡ s
   ├─ [Ax]  ⋅ | t ≡ s, s ≡ u ⊢ t ≡ s
   └─ [≡L(sym)]  ⋅ | t ≡ u, s ≡ u ⊢ t ≡ s
      └─ [≡L(trans)]  ⋅ | u ≡ t, t ≡ u, s ≡ u ⊢ t ≡ s
         └─ [≡L(sym)]  ⋅ | s ≡ t, u ≡ t, t ≡ u, s ≡ u ⊢ t ≡ s
            └─ [Ax]  ⋅ | t ≡ s, s ≡ t, u ≡ t, t ≡ u, s ≡ u ⊢ t ≡ s

ex5 :: Sequent Source #

>>> putStrLn (ppSequent ex5)
⋅ | (≤(t, s) ∨ ≤(s, u)) ∧ ≤(t, u) ⊢ ≤(t, u) ∨ ≤(s, t) ∨ ≤(u, s)
>>> proveAndPrintBFS 5 (fromDefinedRules rulesLJE) ex5
[∧L]  ⋅ | (≤(t, s) ∨ ≤(s, u)) ∧ ≤(t, u) ⊢ ≤(t, u) ∨ ≤(s, t) ∨ ≤(u, s)
└─ [∨L]  ⋅ | ≤(t, s) ∨ ≤(s, u), ≤(t, u) ⊢ ≤(t, u) ∨ ≤(s, t) ∨ ≤(u, s)
   ├─ [∨R₁]  ⋅ | ≤(t, s), ≤(t, u) ⊢ ≤(t, u) ∨ ≤(s, t) ∨ ≤(u, s)
   │  └─ [∨R₁]  ⋅ | ≤(t, s), ≤(t, u) ⊢ ≤(t, u) ∨ ≤(s, t)
   │     └─ [Ax]  ⋅ | ≤(t, s), ≤(t, u) ⊢ ≤(t, u)
   └─ [∨R₁]  ⋅ | ≤(s, u), ≤(t, u) ⊢ ≤(t, u) ∨ ≤(s, t) ∨ ≤(u, s)
      └─ [∨R₁]  ⋅ | ≤(s, u), ≤(t, u) ⊢ ≤(t, u) ∨ ≤(s, t)
         └─ [Ax]  ⋅ | ≤(s, u), ≤(t, u) ⊢ ≤(t, u)