module G4ipProver.Prover
(
prove,
decide,
add,
right,
left,
elim,
ProofTree(..),
Context
)
where
import G4ipProver.Proposition (Prop (..))
import Control.Arrow (second)
import Data.List (inits, tails)
import Control.Monad (liftM2)
import Data.Maybe (catMaybes, isJust, listToMaybe)
prove :: Prop -> Maybe (ProofTree Context)
prove = right ([], [])
decide :: Prop -> Bool
decide = isJust . prove
data ProofTree a =
InitRule a Prop |
TopR a |
BottomL a Prop |
SplitAnd a Prop Prop (ProofTree a) (ProofTree a) |
ImpRight a Prop Prop (ProofTree a) |
AndLeft a Prop Prop Prop (ProofTree a) |
ElimOr a Prop Prop Prop (ProofTree a) (ProofTree a) |
TImpLeft a Prop Prop (ProofTree a) |
FImpLeft a Prop Prop (ProofTree a) |
AndImpLeft a Prop Prop Prop Prop (ProofTree a) |
OrImpLeft a Prop Prop Prop Prop (ProofTree a) |
OrRight1 a Prop Prop (ProofTree a) |
OrRight2 a Prop Prop (ProofTree a) |
LeftBoth a Prop (ProofTree a) |
PImpLeft a Prop Prop Prop (ProofTree a) (ProofTree a) |
ImpImpLeft a Prop Prop Prop Prop (ProofTree a) (ProofTree a)
deriving (Show)
type Context = ([Prop], [Prop])
add :: Prop -> Context -> Context
add p ctx@(inv, other) = case p of
Atom _ -> (inv, p : other)
T -> ctx
F -> ([F], [])
And _ _ -> (p : inv, other)
Or _ _ -> (p : inv, other)
Imp (Atom _) _ -> (inv, p : other)
Imp (Imp _ _) _ -> (inv, p : other)
Imp _ _ -> (p : inv, other)
right :: Context -> Prop -> Maybe (ProofTree Context)
right ctx T = Just (TopR ctx)
right ctx (And a b) =
liftM2 (SplitAnd ctx a b) (right ctx a) (right ctx b)
right ctx (Imp a b) =
right (add a ctx) b >>=
Just . ImpRight ctx a b
right ctx@(And a b : inv, other) c =
right (add a $ add b (inv, other)) c >>=
Just . AndLeft ctx a b c
right ctx@(F : _, _) c = Just $ BottomL ctx c
right ctx@(Or a b : inv, other) c =
right (add a (inv, other)) c >>=
(\p1 -> right (add b (inv, other)) c >>=
Just . ElimOr ctx a b c p1)
right ctx@(Imp T b : inv, other) c =
right (add b (inv, other)) c >>= Just . TImpLeft ctx b c
right ctx@(Imp F a : inv, other) c =
right (inv, other) c >>= Just . FImpLeft ctx a c
right ctx@(Imp (And d e) b : inv, other) c =
right (add (Imp d $ Imp e b) (inv, other)) c >>=
Just . AndImpLeft ctx d e b c
right ctx@(Imp (Or d e) b : inv, other) c =
right (add (Imp e b) $ add (Imp d b) (inv, other)) c >>=
Just . OrImpLeft ctx d e b c
right ctx@([], other) t@(Or a b) =
case left other t of
Just p -> Just (LeftBoth ctx t p)
Nothing -> case right ([], other) a of
Just p -> Just (OrRight1 ctx a b p)
Nothing -> case right ([], other) b of
Just p -> Just (OrRight2 ctx a b p)
Nothing -> Nothing
right ([], other) c =
left other c
right _ _ = Nothing
left :: [Prop] -> Prop -> Maybe (ProofTree Context)
left other c = listToMaybe . catMaybes . map (`elim` c) $ pulls other
where
pulls :: [a] -> [(a, [a])]
pulls xs = take (length xs) $ zipWith (second . (++)) (inits xs) breakdown
where pull (x : xs) = (x, xs)
breakdown = map pull (tails xs)
elim :: (Prop, [Prop]) -> Prop -> Maybe (ProofTree Context)
elim (Atom s1, ctx) r@(Atom s2) =
if s1 == s2 then
Just (InitRule ([], ctx) r)
else Nothing
elim (Imp sa@(Atom s) b, other) c =
right ([], other) (Atom s) >>=
\p1 -> right (add b ([], other)) c >>=
Just . PImpLeft ([], other) sa b c p1
elim (Imp (Imp d e) b, other) c =
right (add d $ add (Imp e b) ([], other)) e >>=
\p1 -> right (add b ([], other)) c >>=
Just . ImpImpLeft ([], other) d e b c p1
elim _ _ = Nothing