This commit is contained in:
Mirek Kratochvil 2022-10-24 23:43:35 +02:00
parent f0d6558df9
commit 14b77cd058
2 changed files with 84 additions and 29 deletions

View file

@ -1,7 +1,12 @@
module Main where module Main where
import qualified Compiler as C
import Control.Monad.IO.Class
import qualified Data.Map as M import qualified Data.Map as M
import Interpreter import qualified Interpreter as I
import qualified Parser as P
import System.Console.Haskeline
import qualified Text.Megaparsec as MP
import Text.Pretty.Simple import Text.Pretty.Simple
ppr :: Show a => a -> IO () ppr :: Show a => a -> IO ()
@ -14,30 +19,30 @@ ppr =
, outputOptionsPageWidth = 80 , outputOptionsPageWidth = 80
} }
main :: IO () interpret :: String -> InputT IO ()
main = do interpret = liftIO . lex
let (res, interp) = where
prove [Goal, U (Struct $ Id 1 2), U (Atom 1), U (Atom 2), LastCall] $ lex input =
M.fromList case MP.parse P.lexPrlg "-" input of
[ ( Id 1 2 Left bundle -> putStr (MP.errorBundlePretty bundle)
, [ [U (Atom 333), U (Atom 444), NoGoal] Right toks -> parse toks
, [ U (Atom 1) parse toks =
, U (Atom 2) case MP.parse P.parsePrlg "-" toks of
, Goal Left bundle -> putStr (MP.errorBundlePretty bundle)
, U (Struct $ Id 2 0) Right ast -> prologize ast
, Call prologize ast = ppr $ map (P.ast2prlg P.defaultOps) ast
, Goal
, U (Struct $ Id 1 2)
, U (Atom 333)
, U (Atom 444)
, LastCall
]
])
, (Id 2 0, [[NoGoal]])
]
ppr interp
ppr res
{- main :: IO ()
ppr $ let { Right l = parse lexPrlg "stdin" "c(cc(X)) :- a, b. " ; Right p = parse parsePrlg "stdin" l; clause:_ = map (ast2prlg defaultOps) p; ((StrTable _ strfwd strback),codei) = strtablizePrlg emptystrtable clause } in compileRule (Id (strfwd M.! ":-") 2) (Id (strfwd M.! ",") 2) codei main =
-} runInputT defaultSettings $ do
outputStrLn "PRLG."
loop
where
loop :: InputT IO ()
loop = do
minput <- getInputLine "|= "
case minput of
Nothing -> return ()
Just input -> do
interpret input
loop

View file

@ -1,14 +1,19 @@
{-# LANGUAGE FlexibleInstances #-}
module Parser where module Parser where
import Control.Applicative (liftA2) import Control.Applicative (liftA2)
import Control.Monad (void) import Control.Monad (void)
import Data.Char import Data.Char
import Data.List (intercalate)
import Data.List.NonEmpty (NonEmpty(..))
import Data.List.Split (splitOn) import Data.List.Split (splitOn)
import Data.Void import Data.Void
import Text.Megaparsec import Text.Megaparsec
import Text.Megaparsec.Char import Text.Megaparsec.Char
import Compiler (PrlgStr(..)) import Compiler (PrlgStr(..))
import Debug.Trace
singleToks = ",;|()[]" singleToks = ",;|()[]"
@ -63,6 +68,51 @@ lexeme = choice [blank, tok, qtok, cmt]
lexPrlg :: Lexer [Lexeme] lexPrlg :: Lexer [Lexeme]
lexPrlg = many lexeme <* (many blank >> eof) lexPrlg = many lexeme <* (many blank >> eof)
showTok (Blank x) = x
showTok (Tok x) = x
showTok (QTok _ x) = x
instance VisualStream [Lexeme] where
showTokens _ (a :| b) = concatMap showTok (a : b)
tokensLength _ (a :| b) = sum $ map (length . showTok) (a : b)
instance TraversableStream [Lexeme] where
reachOffset o pst = go
where
handleEmpty "" = "<empty line>"
handleEmpty x = x
go
| o <= pstateOffset pst =
( Just . handleEmpty $ pstateLinePrefix pst ++
takeWhile (/= '\n') (concatMap showTok $ pstateInput pst)
, pst)
| o > pstateOffset pst =
let (tok:rest) = pstateInput pst
stok = showTok tok
lines = splitOn "\n" stok
nls = length lines - 1
sp = pstateSourcePos pst
in reachOffset
o
pst
{ pstateInput = rest
, pstateOffset = pstateOffset pst + 1
, pstateLinePrefix =
if nls > 0
then last lines
else pstateLinePrefix pst ++ last lines
, pstateSourcePos =
sp
{ sourceLine = mkPos $ unPos (sourceLine sp) + nls
, sourceColumn =
mkPos $
(if nls > 0
then 1
else unPos (sourceColumn sp)) +
length (last lines)
}
}
data AST data AST
= Call String [[AST]] = Call String [[AST]]
| Seq [AST] | Seq [AST]
@ -196,7 +246,7 @@ shunt optable = start
| Just _ <- getPrefix x | Just _ <- getPrefix x
, Just (ops', vs') <- pushPrefix ops vs x = wo ops' vs' xs , Just (ops', vs') <- pushPrefix ops vs x = wo ops' vs' xs
| isOperand x = ho ops (rec l : vs) xs | isOperand x = ho ops (rec l : vs) xs
| otherwise = error $ "want valid operand " ++ show (ops,vs,l,xs) | otherwise = error $ "want valid operand"
{- incoming non-literal (i.e., surely operand), push it and switch to "have operand" -} {- incoming non-literal (i.e., surely operand), push it and switch to "have operand" -}
wo ops vs (x:xs) = ho ops (rec x : vs) xs wo ops vs (x:xs) = ho ops (rec x : vs) xs
{- end of stream, but the operand is missing -} {- end of stream, but the operand is missing -}
@ -236,8 +286,8 @@ shunt optable = start
{- actual pushery -} {- actual pushery -}
canPush [] op = Just True canPush [] op = Just True
canPush ((_, Op p f):ops) (Op np nf) = go p f np nf canPush ((_, Op p f):ops) (Op np nf) = go p f np nf
where
{- helper -} {- helper -}
where
prioLtOp X = (<) prioLtOp X = (<)
prioLtOp Y = (<=) prioLtOp Y = (<=)
{- pushing a prefix -} {- pushing a prefix -}