Merge pull request 'Resolves issue with parsing comments' (#2) from fix/comments-0001 into main
Reviewed-on: #2
This commit is contained in:
commit
38509724b1
@ -4,8 +4,9 @@ import Parser
|
|||||||
import Research
|
import Research
|
||||||
|
|
||||||
import Data.Map (Map)
|
import Data.Map (Map)
|
||||||
import qualified Data.Map as Map
|
|
||||||
import Data.List (foldl')
|
import Data.List (foldl')
|
||||||
|
|
||||||
|
import qualified Data.Map as Map
|
||||||
import qualified Data.Set as Set
|
import qualified Data.Set as Set
|
||||||
|
|
||||||
evalSingle :: Map String T -> TricuAST -> Map String T
|
evalSingle :: Map String T -> TricuAST -> Map String T
|
||||||
@ -51,6 +52,7 @@ evalAST env term = case term of
|
|||||||
SStr str -> ofString str
|
SStr str -> ofString str
|
||||||
SInt num -> ofNumber num
|
SInt num -> ofNumber num
|
||||||
SList elems -> ofList (map (evalAST Map.empty) elems)
|
SList elems -> ofList (map (evalAST Map.empty) elems)
|
||||||
|
SEmpty -> Leaf
|
||||||
SFunc name args body ->
|
SFunc name args body ->
|
||||||
error $ "Unexpected function definition " ++ name
|
error $ "Unexpected function definition " ++ name
|
||||||
++ " in evalAST; define via evalSingle."
|
++ " in evalAST; define via evalSingle."
|
||||||
@ -66,9 +68,8 @@ eliminateLambda (TFork l r) = TFork (eliminateLambda l) (eliminateLambda r)
|
|||||||
eliminateLambda (SList xs) = SList (map eliminateLambda xs)
|
eliminateLambda (SList xs) = SList (map eliminateLambda xs)
|
||||||
eliminateLambda other = other
|
eliminateLambda other = other
|
||||||
|
|
||||||
-- This is my attempt to implement the lambda calculus elimination rules defined
|
|
||||||
-- in "Typed Program Analysis without Encodings" by Barry Jay.
|
|
||||||
-- https://github.com/barry-jay-personal/typed_tree_calculus/blob/main/typed_program_analysis.pdf
|
-- https://github.com/barry-jay-personal/typed_tree_calculus/blob/main/typed_program_analysis.pdf
|
||||||
|
-- Chapter 4: Lambda-Abstraction
|
||||||
lambdaToT :: String -> TricuAST -> TricuAST
|
lambdaToT :: String -> TricuAST -> TricuAST
|
||||||
lambdaToT x (SVar y)
|
lambdaToT x (SVar y)
|
||||||
| x == y = tI
|
| x == y = tI
|
||||||
|
29
src/Lexer.hs
29
src/Lexer.hs
@ -2,10 +2,12 @@ module Lexer where
|
|||||||
|
|
||||||
import Research
|
import Research
|
||||||
import Text.Megaparsec
|
import Text.Megaparsec
|
||||||
import Text.Megaparsec.Char
|
import Text.Megaparsec.Char hiding (space)
|
||||||
|
import Text.Megaparsec.Char.Lexer
|
||||||
|
|
||||||
import Control.Monad (void)
|
import Control.Monad (void)
|
||||||
import Data.Void
|
import Data.Void
|
||||||
|
|
||||||
import qualified Data.Set as Set
|
import qualified Data.Set as Set
|
||||||
|
|
||||||
type Lexer = Parsec Void String
|
type Lexer = Parsec Void String
|
||||||
@ -23,7 +25,6 @@ data LToken
|
|||||||
| LOpenBracket
|
| LOpenBracket
|
||||||
| LCloseBracket
|
| LCloseBracket
|
||||||
| LNewline
|
| LNewline
|
||||||
| LComment String
|
|
||||||
deriving (Show, Eq, Ord)
|
deriving (Show, Eq, Ord)
|
||||||
|
|
||||||
keywordT :: Lexer LToken
|
keywordT :: Lexer LToken
|
||||||
@ -75,17 +76,21 @@ closeBracket = char ']' *> pure LCloseBracket
|
|||||||
lnewline :: Lexer LToken
|
lnewline :: Lexer LToken
|
||||||
lnewline = char '\n' *> pure LNewline
|
lnewline = char '\n' *> pure LNewline
|
||||||
|
|
||||||
comment :: Lexer LToken
|
|
||||||
comment = do
|
|
||||||
string "--"
|
|
||||||
content <- many (satisfy (/= '\n'))
|
|
||||||
pure (LComment content)
|
|
||||||
|
|
||||||
sc :: Lexer ()
|
sc :: Lexer ()
|
||||||
sc = skipMany (void (char ' ') <|> void (char '\t') <|> void comment)
|
sc = space space1 (skipLineComment "--") (skipBlockComment "|-" "-|")
|
||||||
|
|
||||||
tricuLexer :: Lexer [LToken]
|
tricuLexer :: Lexer [LToken]
|
||||||
tricuLexer = many (sc *> choice
|
tricuLexer = do
|
||||||
|
sc
|
||||||
|
tokens <- many $ do
|
||||||
|
tok <- choice tricuLexer'
|
||||||
|
sc
|
||||||
|
pure tok
|
||||||
|
sc
|
||||||
|
eof
|
||||||
|
pure tokens
|
||||||
|
where
|
||||||
|
tricuLexer' =
|
||||||
[ try identifier
|
[ try identifier
|
||||||
, try keywordT
|
, try keywordT
|
||||||
, try integerLiteral
|
, try integerLiteral
|
||||||
@ -97,8 +102,8 @@ tricuLexer = many (sc *> choice
|
|||||||
, closeParen
|
, closeParen
|
||||||
, openBracket
|
, openBracket
|
||||||
, closeBracket
|
, closeBracket
|
||||||
, lnewline
|
]
|
||||||
] <* sc) <* eof
|
|
||||||
|
|
||||||
lexTricu :: String -> [LToken]
|
lexTricu :: String -> [LToken]
|
||||||
lexTricu input = case runParser tricuLexer "" input of
|
lexTricu input = case runParser tricuLexer "" input of
|
||||||
|
12
src/Main.hs
12
src/Main.hs
@ -1,14 +1,14 @@
|
|||||||
module Main where
|
module Main where
|
||||||
|
|
||||||
import Eval
|
import Eval (evalTricu, result)
|
||||||
import Lexer
|
import Library (library)
|
||||||
import Library
|
import Parser (parseTricu)
|
||||||
import Parser
|
|
||||||
import REPL (repl)
|
import REPL (repl)
|
||||||
import Research
|
import Research (T)
|
||||||
|
|
||||||
|
import Text.Megaparsec (runParser)
|
||||||
|
|
||||||
import qualified Data.Map as Map
|
import qualified Data.Map as Map
|
||||||
import Text.Megaparsec (runParser)
|
|
||||||
|
|
||||||
main :: IO ()
|
main :: IO ()
|
||||||
main = do
|
main = do
|
||||||
|
@ -1,16 +1,16 @@
|
|||||||
module Parser where
|
module Parser where
|
||||||
|
|
||||||
import Debug.Trace
|
|
||||||
import Lexer
|
import Lexer
|
||||||
import Research hiding (toList)
|
import Research hiding (toList)
|
||||||
import Control.Exception (throw)
|
|
||||||
import Data.List.NonEmpty (toList)
|
import Data.List.NonEmpty (toList)
|
||||||
import qualified Data.Set as Set
|
import Data.Void (Void)
|
||||||
import Data.Void
|
|
||||||
import Text.Megaparsec
|
import Text.Megaparsec
|
||||||
import Text.Megaparsec.Char
|
import Text.Megaparsec.Char
|
||||||
import Text.Megaparsec.Error (errorBundlePretty, ParseErrorBundle)
|
import Text.Megaparsec.Error (errorBundlePretty, ParseErrorBundle)
|
||||||
|
|
||||||
|
import qualified Data.Set as Set
|
||||||
|
|
||||||
type Parser = Parsec Void [LToken]
|
type Parser = Parsec Void [LToken]
|
||||||
|
|
||||||
data TricuAST
|
data TricuAST
|
||||||
@ -24,15 +24,22 @@ data TricuAST
|
|||||||
| TStem TricuAST
|
| TStem TricuAST
|
||||||
| TFork TricuAST TricuAST
|
| TFork TricuAST TricuAST
|
||||||
| SLambda [String] TricuAST
|
| SLambda [String] TricuAST
|
||||||
|
| SEmpty
|
||||||
deriving (Show, Eq, Ord)
|
deriving (Show, Eq, Ord)
|
||||||
|
|
||||||
parseTricu :: String -> [TricuAST]
|
parseTricu :: String -> [TricuAST]
|
||||||
parseTricu input =
|
parseTricu input
|
||||||
let nonEmptyLines = filter (not . null) (lines input)
|
| null tokens = []
|
||||||
in map parseSingle nonEmptyLines
|
| otherwise = map parseSingle tokens
|
||||||
|
where
|
||||||
|
tokens = case lexTricu input of
|
||||||
|
[] -> []
|
||||||
|
tokens -> lines input
|
||||||
|
|
||||||
parseSingle :: String -> TricuAST
|
parseSingle :: String -> TricuAST
|
||||||
parseSingle input = case runParser parseExpression "" (lexTricu input) of
|
parseSingle input = case lexTricu input of
|
||||||
|
[] -> SEmpty
|
||||||
|
tokens -> case runParser parseExpression "" tokens of
|
||||||
Left err -> error $ handleParseError err
|
Left err -> error $ handleParseError err
|
||||||
Right ast -> ast
|
Right ast -> ast
|
||||||
|
|
||||||
|
22
src/REPL.hs
22
src/REPL.hs
@ -5,10 +5,12 @@ import Lexer
|
|||||||
import Parser
|
import Parser
|
||||||
import Research
|
import Research
|
||||||
|
|
||||||
|
import Control.Exception (SomeException, catch)
|
||||||
|
import Control.Monad.IO.Class (liftIO)
|
||||||
import Data.List (intercalate)
|
import Data.List (intercalate)
|
||||||
import qualified Data.Map as Map
|
|
||||||
import System.Console.Haskeline
|
import System.Console.Haskeline
|
||||||
import System.IO (hFlush, stdout)
|
|
||||||
|
import qualified Data.Map as Map
|
||||||
|
|
||||||
repl :: Map.Map String T -> IO ()
|
repl :: Map.Map String T -> IO ()
|
||||||
repl env = runInputT defaultSettings (loop env)
|
repl env = runInputT defaultSettings (loop env)
|
||||||
@ -23,14 +25,24 @@ repl env = runInputT defaultSettings (loop env)
|
|||||||
outputStrLn ""
|
outputStrLn ""
|
||||||
loop env
|
loop env
|
||||||
Just input -> do
|
Just input -> do
|
||||||
|
newEnv <- liftIO $ (processInput env input `catch` errorHandler env)
|
||||||
|
loop newEnv
|
||||||
|
|
||||||
|
processInput :: Map.Map String T -> String -> IO (Map.Map String T)
|
||||||
|
processInput env input = do
|
||||||
let clearEnv = Map.delete "__result" env
|
let clearEnv = Map.delete "__result" env
|
||||||
newEnv = evalSingle clearEnv (parseSingle input)
|
newEnv = evalSingle clearEnv (parseSingle input)
|
||||||
case Map.lookup "__result" newEnv of
|
case Map.lookup "__result" newEnv of
|
||||||
Just r -> do
|
Just r -> do
|
||||||
outputStrLn $ "tricu > " ++ show r
|
putStrLn $ "tricu > " ++ show r
|
||||||
outputStrLn $ "DECODE -: \"" ++ decodeResult r ++ "\""
|
putStrLn $ "READ -: \"" ++ decodeResult r ++ "\""
|
||||||
Nothing -> return ()
|
Nothing -> return ()
|
||||||
loop newEnv
|
return newEnv
|
||||||
|
|
||||||
|
errorHandler :: Map.Map String T -> SomeException -> IO (Map.Map String T)
|
||||||
|
errorHandler env e = do
|
||||||
|
putStrLn $ "Error: " ++ show e
|
||||||
|
return env
|
||||||
|
|
||||||
decodeResult :: T -> String
|
decodeResult :: T -> String
|
||||||
decodeResult tc = case toNumber tc of
|
decodeResult tc = case toNumber tc of
|
||||||
|
@ -1,10 +1,11 @@
|
|||||||
module Research where
|
module Research where
|
||||||
|
|
||||||
import Data.List (intercalate)
|
|
||||||
import Control.Monad.State
|
import Control.Monad.State
|
||||||
import qualified Data.Map as Map
|
import Data.List (intercalate)
|
||||||
import Data.Map (Map)
|
import Data.Map (Map)
|
||||||
|
|
||||||
|
import qualified Data.Map as Map
|
||||||
|
|
||||||
data T = Leaf | Stem T | Fork T T
|
data T = Leaf | Stem T | Fork T T
|
||||||
deriving (Show, Eq, Ord)
|
deriving (Show, Eq, Ord)
|
||||||
|
|
||||||
@ -36,7 +37,7 @@ _K = Stem Leaf
|
|||||||
|
|
||||||
-- Identity
|
-- Identity
|
||||||
-- We use the "point-free" style which drops a redundant node
|
-- We use the "point-free" style which drops a redundant node
|
||||||
-- Full _I form (SKK): Fork (Stem (Stem Leaf)) (Stem Leaf)
|
-- Full I form (SKK): Fork (Stem (Stem Leaf)) (Stem Leaf)
|
||||||
_I :: T
|
_I :: T
|
||||||
_I = Fork (Stem (Stem Leaf)) Leaf
|
_I = Fork (Stem (Stem Leaf)) Leaf
|
||||||
|
|
||||||
|
15
test/Spec.hs
15
test/Spec.hs
@ -25,7 +25,6 @@ tests :: TestTree
|
|||||||
tests = testGroup "Tricu Tests"
|
tests = testGroup "Tricu Tests"
|
||||||
[ lexerTests
|
[ lexerTests
|
||||||
, parserTests
|
, parserTests
|
||||||
, integrationTests
|
|
||||||
, evaluationTests
|
, evaluationTests
|
||||||
, lambdaEvalTests
|
, lambdaEvalTests
|
||||||
, libraryTests
|
, libraryTests
|
||||||
@ -159,18 +158,6 @@ parserTests = testGroup "Parser Tests"
|
|||||||
-- parseTricu input @?= expect
|
-- parseTricu input @?= expect
|
||||||
]
|
]
|
||||||
|
|
||||||
integrationTests :: TestTree
|
|
||||||
integrationTests = testGroup "Integration Tests"
|
|
||||||
[ testCase "Combine lexer and parser" $ do
|
|
||||||
let input = "x = t t t"
|
|
||||||
expect = SFunc "x" [] (SApp (SApp TLeaf TLeaf) TLeaf)
|
|
||||||
parseSingle input @?= expect
|
|
||||||
, testCase "Complex Tree Calculus expression" $ do
|
|
||||||
let input = "t (t t t) t"
|
|
||||||
expect = SApp (SApp TLeaf (SApp (SApp TLeaf TLeaf) TLeaf)) TLeaf
|
|
||||||
parseSingle input @?= expect
|
|
||||||
]
|
|
||||||
|
|
||||||
evaluationTests :: TestTree
|
evaluationTests :: TestTree
|
||||||
evaluationTests = testGroup "Evaluation Tests"
|
evaluationTests = testGroup "Evaluation Tests"
|
||||||
[ testCase "Evaluate single Leaf" $ do
|
[ testCase "Evaluate single Leaf" $ do
|
||||||
@ -317,7 +304,7 @@ libraryTests = testGroup "Library Tests"
|
|||||||
let input = "s (t) (t) (t)"
|
let input = "s (t) (t) (t)"
|
||||||
env = evalTricu library (parseTricu input)
|
env = evalTricu library (parseTricu input)
|
||||||
result env @?= Fork Leaf (Stem Leaf)
|
result env @?= Fork Leaf (Stem Leaf)
|
||||||
, testCase "SKK == I" $ do -- Tests for fully expanded I form
|
, testCase "SKK == I (fully expanded)" $ do
|
||||||
let input = "s k k"
|
let input = "s k k"
|
||||||
env = evalTricu library (parseTricu input)
|
env = evalTricu library (parseTricu input)
|
||||||
result env @?= Fork (Stem (Stem Leaf)) (Stem Leaf)
|
result env @?= Fork (Stem (Stem Leaf)) (Stem Leaf)
|
||||||
|
Loading…
x
Reference in New Issue
Block a user