{-# LANGUAGE TupleSections #-} module Interpreter where import Data.Function import qualified Data.Map as M {- VAM 2P, done the lazy way -} data StrTable = StrTable Int (M.Map Int String) data Datum = Atom Int -- unifies a constant | Struct (Int, Int) -- unifies a structure with arity deriving (Show) data Instr = U Datum -- something unifiable | NoGoal -- trivial goal | Goal -- we start a new goal, set up backtracking etc | Call -- all seems okay, call the goal | LastCall -- tail call the goal deriving (Show) type Code = [Instr] type Alts = [(Code, Code)] -- clauses to try and the corresponding goals to restore type Defs = M.Map (Int, Int) [Code] data Interp = Interp { defs :: Defs -- global definitions for lookup , hed :: Code -- current head , gol :: Code -- current goal , stk :: [Alts] -- possible heads with stored original goal } deriving (Show) prove :: Code -> Defs -> Either (Interp, String) Bool prove g ds = let i0 = Interp ds g [LastCall] [[]] run (Left x) = x run (Right x) = run $ proveStep Right Left x in run (Right i0) {- this gonna need Either String Bool for errors later -} proveStep :: (Interp -> a) -> (Either (Interp, String) Bool -> a) -> Interp -> a proveStep c f i = go i where ifail msg = f $ Left (i, msg) withDef f | Just d <- defs i M.!? f = ($ d) | otherwise = const $ ifail $ "no definition: " ++ show f {- Backtracking -} backtrack i@Interp {stk = ((s, gs):ss):sss} -- backtrack to next clause, restoring goal = c i {hed = s, gol = gs, stk = ss : sss} backtrack i@Interp {stk = []:ss@(_:_):sss} -- no next clause, pop stack and backtrack the caller clause = backtrack i {hed = error "failed hed", gol = error "failed gol", stk = ss : sss} backtrack i@Interp {stk = [[]]} = f (Right False) backtrack i@Interp {stk = []:[]:_} = ifail "broken stk" -- this should not happen {- Unification -} go i@Interp {hed = (U a:hs), gol = (U b:gs)} -- unify constants = unify a b where uok = c i {hed = hs, gol = gs} unify (Atom a) (Atom b) | a == b = uok unify (Struct a) (Struct b) | a == b = uok unify _ _ = backtrack i {- Resolution -} go i@Interp {hed = [NoGoal], gol = [LastCall], stk = [_]} = f (Right True) -- final success go i@Interp { hed = [NoGoal] , gol = [LastCall] , stk = _:((Goal:U (Struct f):gs, _):ss):sss } -- goal succeeded, continue with parent frame = withDef f $ \(hs:ohs) -> c i {hed = hs, gol = gs, stk = (map (, gs) ohs ++ ss) : sss} go i@Interp { hed = [NoGoal] , gol = (Call:Goal:U (Struct f):gs) , stk = ss:sss } -- next goal = withDef f $ \(hs:ohs) -> c i {hed = hs, gol = gs, stk = (map (, gs) ohs ++ ss) : sss} go i@Interp {hed = (Goal:U (Struct f):ngs), gol = (Call:gs), stk = ss:sss} -- normal call = withDef f $ \(hs:ohs) -> c i { hed = hs , gol = ngs , stk = (map (, ngs) ohs) : ((gs, error "gol no hed") : ss) : sss } go i@Interp {hed = (Goal:U (Struct f):ngs), gol = [LastCall], stk = _:sss} -- tail call = withDef f $ \(hs:ohs) -> c i {hed = hs, gol = ngs, stk = map (, ngs) ohs : sss} go _ = ifail "impossible instruction combo"