compiler can compile errors
This commit is contained in:
parent
f61d6a0179
commit
452cd49496
|
@ -96,11 +96,13 @@ assertFact :: (Code -> Id -> PrlgEnv ()) -> InterpFn
|
||||||
assertFact addClause =
|
assertFact addClause =
|
||||||
withArgs [0] $ \[arg] -> do
|
withArgs [0] $ \[arg] -> do
|
||||||
heap <- use (cur . heap)
|
heap <- use (cur . heap)
|
||||||
case Co.compileGoal . Co.squashVars <$>
|
case Co.heapStructPrlgInt Nothing heap arg of
|
||||||
Co.heapStructPrlgInt Nothing heap arg of
|
Just x -> do
|
||||||
Just (U (Struct s):head) -> do
|
case Co.compileGoal $ Co.squashVars x of
|
||||||
addClause (head ++ [Done]) s
|
Right (U (Struct s):head) -> do
|
||||||
continue
|
addClause (head ++ [Done]) s
|
||||||
|
continue
|
||||||
|
Left err -> prlgError err
|
||||||
_ -> prlgError "assert fact failure"
|
_ -> prlgError "assert fact failure"
|
||||||
|
|
||||||
assertRule :: (Code -> Id -> PrlgEnv ()) -> InterpFn
|
assertRule :: (Code -> Id -> PrlgEnv ()) -> InterpFn
|
||||||
|
@ -108,16 +110,13 @@ assertRule addClause =
|
||||||
withArgs [0, 1] $ \args -> do
|
withArgs [0, 1] $ \args -> do
|
||||||
scope <- use (cur . hvar)
|
scope <- use (cur . hvar)
|
||||||
heap <- use (cur . heap)
|
heap <- use (cur . heap)
|
||||||
comma <- findAtom ","
|
[comma, semi, cut] <- traverse findAtom [",", ";", "!"]
|
||||||
semi <- findAtom ";"
|
|
||||||
cut <- findAtom "!"
|
|
||||||
case Co.squashVars . IR.CallI 0 <$>
|
case Co.squashVars . IR.CallI 0 <$>
|
||||||
traverse (Co.heapStructPrlgInt Nothing heap) args of
|
traverse (Co.heapStructPrlgInt Nothing heap) args of
|
||||||
Just (IR.CallI 0 [hs, gs]) ->
|
Just (IR.CallI 0 [hs, gs]) ->
|
||||||
let (U (Struct s):cs) =
|
case (++) <$> Co.compileGoal hs <*> Co.compileGoals comma semi cut gs of
|
||||||
Co.compileGoal hs ++ Co.compileGoals comma semi cut gs
|
Right (U (Struct s):cs) -> addClause cs s >> continue
|
||||||
in do addClause cs s
|
Left err -> prlgError err
|
||||||
continue
|
|
||||||
_ -> prlgError "assert clause failure"
|
_ -> prlgError "assert clause failure"
|
||||||
|
|
||||||
retractall :: InterpFn
|
retractall :: InterpFn
|
||||||
|
@ -139,11 +138,14 @@ exec' fgol =
|
||||||
comma <- findAtom ","
|
comma <- findAtom ","
|
||||||
semi <- findAtom ";"
|
semi <- findAtom ";"
|
||||||
cut <- findAtom "!"
|
cut <- findAtom "!"
|
||||||
zoom cur $ do
|
case Co.compileGoals comma semi cut gs of
|
||||||
hvar .= M.empty
|
Right nhed -> do
|
||||||
hed .= Co.compileGoals comma semi cut gs
|
zoom cur $ do
|
||||||
gol %= fgol
|
hvar .= M.empty
|
||||||
continue
|
hed .= nhed
|
||||||
|
gol %= fgol
|
||||||
|
continue
|
||||||
|
Left err -> prlgError err
|
||||||
_ -> prlgError "bad goal"
|
_ -> prlgError "bad goal"
|
||||||
|
|
||||||
call :: InterpFn
|
call :: InterpFn
|
||||||
|
|
|
@ -1,6 +1,7 @@
|
||||||
module Compiler where
|
module Compiler where
|
||||||
|
|
||||||
import Constant
|
import Constant
|
||||||
|
import Control.Monad
|
||||||
import Data.Char (isUpper)
|
import Data.Char (isUpper)
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
|
|
||||||
|
@ -45,28 +46,28 @@ squashVars x =
|
||||||
[(idx, VarI idx') | ((idx, n), idx') <- zip occurs [1 ..], n > 1]
|
[(idx, VarI idx') | ((idx, n), idx') <- zip occurs [1 ..], n > 1]
|
||||||
in renumVars (m' M.!?) x
|
in renumVars (m' M.!?) x
|
||||||
|
|
||||||
squashChoices :: [Code] -> Code
|
squashChoices :: [Code] -> Either String Code
|
||||||
squashChoices = out . concatMap go
|
squashChoices = out . concatMap go
|
||||||
where
|
where
|
||||||
go [Choices cs] = cs
|
go [Choices cs] = cs
|
||||||
go x = [x]
|
go x = [x]
|
||||||
out [] = error "choice compilation"
|
out [] = Left "goal compilation has no choices?"
|
||||||
out [x] = x
|
out [x] = pure x
|
||||||
out xs = [Choices xs]
|
out xs = pure [Choices xs]
|
||||||
|
|
||||||
compileGoals :: Int -> Int -> Int -> PrlgInt -> Code
|
compileGoals :: Int -> Int -> Int -> PrlgInt -> Either String Code
|
||||||
compileGoals andop orop cut = (++ [Done]) . go'
|
compileGoals andop orop cut = fmap (++ [Done]) . go'
|
||||||
where
|
where
|
||||||
go' = go . struct2goal
|
go' = struct2goal >=> go
|
||||||
go p@(CallI x args@[_, _])
|
go p@(CallI x args@[_, _])
|
||||||
| x == andop = concatMap go' args
|
| x == andop = concat <$> traverse go' args
|
||||||
| x == orop = squashChoices $ map go' args
|
| x == orop = traverse go' args >>= squashChoices
|
||||||
go p@(CallI x [])
|
go p@(CallI x [])
|
||||||
| x == cut = [Cut]
|
| x == cut = pure [Cut]
|
||||||
go x = compileGoal x
|
go x = compileGoal x
|
||||||
|
|
||||||
compileGoal :: PrlgInt -> Code
|
compileGoal :: PrlgInt -> Either String Code
|
||||||
compileGoal = compileArg . struct2goal
|
compileGoal = fmap compileArg . struct2goal
|
||||||
|
|
||||||
compileArg :: PrlgInt -> Code
|
compileArg :: PrlgInt -> Code
|
||||||
compileArg (CallI i args) =
|
compileArg (CallI i args) =
|
||||||
|
@ -88,12 +89,7 @@ heapStructPrlgInt heaperr heap ref = heapStruct atom struct hrec heap ref
|
||||||
| r == ref = pure $ VarI r
|
| r == ref = pure $ VarI r
|
||||||
| otherwise = heaperr
|
| otherwise = heaperr
|
||||||
|
|
||||||
-- TODO check if this is used
|
struct2goal :: PrlgInt -> Either String PrlgInt
|
||||||
goal2struct :: PrlgInt -> PrlgInt
|
struct2goal (ConstI (Atom s)) = pure $ CallI s []
|
||||||
goal2struct (CallI s []) = ConstI (Atom s)
|
struct2goal call@(CallI _ _) = pure call
|
||||||
goal2struct x = x
|
struct2goal x = Left $ "cannot compile goal: " ++ show x
|
||||||
|
|
||||||
struct2goal :: PrlgInt -> PrlgInt
|
|
||||||
struct2goal (ConstI (Atom s)) = CallI s []
|
|
||||||
struct2goal call@(CallI _ _) = call
|
|
||||||
struct2goal _ = error "TODO."
|
|
||||||
|
|
|
@ -33,8 +33,8 @@ handleError m = do
|
||||||
|
|
||||||
processCmd precompileHook ast' = do
|
processCmd precompileHook ast' = do
|
||||||
ast <- shunt ast'
|
ast <- shunt ast'
|
||||||
code <- lift $ intern ast >>= precompileHook >>= compile
|
source <- lift $ intern ast >>= precompileHook
|
||||||
lift (I.prove code) >>= except
|
compile source >>= lift . I.prove >>= except
|
||||||
|
|
||||||
interpreterStart :: PrlgEnv ()
|
interpreterStart :: PrlgEnv ()
|
||||||
interpreterStart = do
|
interpreterStart = do
|
||||||
|
|
|
@ -31,16 +31,13 @@ intern :: P.PrlgStr -> PrlgEnv IR.PrlgInt
|
||||||
intern prlgs = do
|
intern prlgs = do
|
||||||
prlgi <- withStrTable $ \st -> IR.internPrlg st prlgs
|
prlgi <- withStrTable $ \st -> IR.internPrlg st prlgs
|
||||||
underscore <- findAtom "_"
|
underscore <- findAtom "_"
|
||||||
list <- findAtom "[]"
|
|
||||||
withStrTable $ \st ->
|
withStrTable $ \st ->
|
||||||
(st, C.squashVars $ C.variablizePrlg underscore st prlgi)
|
(st, C.squashVars $ C.variablizePrlg underscore st prlgi)
|
||||||
|
|
||||||
compile :: IR.PrlgInt -> PrlgEnv Code
|
compile :: IR.PrlgInt -> ExceptT String PrlgEnv Code
|
||||||
compile prlgv = do
|
compile prlgv = do
|
||||||
comma <- findAtom ","
|
[comma, semi, cut] <- lift $ traverse findAtom [",", ";", "!"]
|
||||||
semi <- findAtom ";"
|
except $ C.compileGoals comma semi cut prlgv
|
||||||
cut <- findAtom "!"
|
|
||||||
return $ C.compileGoals comma semi cut prlgv
|
|
||||||
|
|
||||||
expansion ::
|
expansion ::
|
||||||
(Int -> IR.PrlgInt -> IR.PrlgInt)
|
(Int -> IR.PrlgInt -> IR.PrlgInt)
|
||||||
|
|
Loading…
Reference in a new issue