diff options
author | Marvin Borner | 2022-08-22 20:32:22 +0200 |
---|---|---|
committer | Marvin Borner | 2022-08-22 20:32:22 +0200 |
commit | 757a3e284ca52e81aa824219a535bba89c058e15 (patch) | |
tree | 2cad8d8ce555939a6f636483affac76ff987d85d | |
parent | 4ed788a832655006171754d15d370a6b64793477 (diff) |
Fixed execution of multiple commands and removed :print
-rw-r--r-- | editors/vim/syntax/bruijn.vim | 2 | ||||
-rw-r--r-- | src/Eval.hs | 192 | ||||
-rw-r--r-- | src/Helper.hs | 10 | ||||
-rw-r--r-- | src/Parser.hs | 52 | ||||
-rw-r--r-- | std/List.bruijn | 7 | ||||
-rw-r--r-- | std/String.bruijn | 8 |
6 files changed, 141 insertions, 130 deletions
diff --git a/editors/vim/syntax/bruijn.vim b/editors/vim/syntax/bruijn.vim index ef78a72..309fbe1 100644 --- a/editors/vim/syntax/bruijn.vim +++ b/editors/vim/syntax/bruijn.vim @@ -10,7 +10,7 @@ syn match bruijnAbstraction /[[\]]/ syn match bruijnIndex /\([^0-9]\)\@<=\d\([^0-9]\)\@=/ syn match bruijnNumber /([+-]\d\+)/ syn match bruijnDefinition /^\t*\S\+/ -syn match bruijnKeyword /:test\|:import\|:input\|:print/ +syn match bruijnKeyword /:test\|:import\|:input/ syn match bruijnNamespace /[A-Z][a-z]*\(\.\)\@=/ syn match bruijnNamespaceDelim /\([A-Z][a-z]*\)\@<=\./ diff --git a/src/Eval.hs b/src/Eval.hs index ea0040c..2f1bb7e 100644 --- a/src/Eval.hs +++ b/src/Eval.hs @@ -65,7 +65,7 @@ loadFile path conf cache = do evalFun :: Identifier -> Environment -> EvalState (Failable Expression) evalFun fun (Environment sub) = state $ \env@(Environment e) -> let lookup' name env' = case M.lookup fun env' of - Nothing -> Left $ UndeclaredIdentifier name + Nothing -> Left $ UndefinedIdentifier name Just (EnvDef { _exp = x }) -> Right x in case lookup' fun sub of -- search in sub env s@(Right _) -> (s, env) @@ -101,9 +101,9 @@ evalExp ( Application f g) = evalApp f g evalExp ( Infix le i re ) = evalInfix le i re evalExp ( Prefix p e ) = evalPrefix p e -evalDefine +evalDefinition :: Identifier -> Expression -> Environment -> EvalState (Failable Expression) -evalDefine i e sub = evalExp e sub >>= \case +evalDefinition i e sub = evalExp e sub >>= \case Left e' -> pure $ Left e' Right f -> modify @@ -113,7 +113,7 @@ evalDefine i e sub = evalExp e sub >>= \case >> pure (Right f) evalTest - :: Expression -> Expression -> Environment -> EvalState (Failable Instruction) + :: Expression -> Expression -> Environment -> EvalState (Failable Command) evalTest e1 e2 sub = evalExp e1 sub >>= \case Left err -> pure $ Left err Right e1' -> fmap (Test e1') <$> evalExp e2 sub @@ -130,13 +130,97 @@ fullPath path = do exists <- doesFileExist lib pure $ if exists then lib else path +evalCommand :: String -> EnvState -> Command -> IO EnvState +evalCommand inp s@(EnvState env@(Environment envDefs) conf cache) = \case + Input path -> do + full <- fullPath path + if full `elem` _evalPaths conf + then + print + (ContextualError (ImportError path) (Context inp $ _nicePath conf)) + >> pure s + else if M.member path (_imported cache) + then + let (Environment env') = fromJust $ M.lookup path (_imported cache) + in pure $ s { _env = Environment $ M.union env' envDefs } + else do + EnvState (Environment env') _ cache' <- loadFile + full + (conf { _nicePath = path }) + cache -- TODO: Fix wrong `within` in import error + cache'' <- pure $ cache + { _imported = M.insert path (Environment env') + $ M.union (_imported cache) (_imported cache') + } + pure $ EnvState (Environment $ M.union env' envDefs) conf cache'' -- import => _isRepl = False + Import path namespace -> do -- TODO: Merge with Input (very similar) + full <- fullPath path + if full `elem` _evalPaths conf + then + print + (ContextualError (ImportError path) (Context inp $ _nicePath conf)) + >> pure s + else if M.member path (_imported cache) + then -- load from cache + let + (Environment env') = fromJust $ M.lookup path (_imported cache) + prefix | null namespace = takeBaseName path ++ "." + | namespace == "." = "" + | otherwise = namespace ++ "." + rewriteKeys "" = id + rewriteKeys p = M.mapKeys $ \f -> NamespacedFunction p f + rewriteFuns = + M.map $ \d -> d { _flags = (_flags d) { _isImported = True } } + filterImported = + M.filter $ \(EnvDef { _flags = f }) -> _isImported f == False + env'' = rewriteFuns $ rewriteKeys prefix $ filterImported env' + in + pure $ s { _env = Environment $ M.union env'' envDefs } + else do + EnvState (Environment env') _ cache' <- loadFile + full + (conf { _nicePath = path }) + cache -- TODO: Fix wrong `within` in import error + cache'' <- pure $ cache + { _imported = M.insert path (Environment env') + $ M.union (_imported cache) (_imported cache') + } + let + prefix | null namespace = takeBaseName path ++ "." + | namespace == "." = "" + | otherwise = namespace ++ "." + rewriteKeys "" = id + rewriteKeys p = M.mapKeys $ \f -> NamespacedFunction p f + rewriteFuns = + M.map $ \d -> d { _flags = (_flags d) { _isImported = True } } + filterImported = + M.filter $ \(EnvDef { _flags = f }) -> _isImported f == False + env'' <- pure $ rewriteFuns $ rewriteKeys prefix $ filterImported env' + pure $ EnvState (Environment $ M.union env'' envDefs) conf cache'' -- import => _isRepl = False + Test e1 e2 + | _evalTests conf + -> let (res, _) = evalTest e1 e2 (Environment M.empty) `runState` env + in + case res of + Left err -> + print (ContextualError err $ Context inp $ _nicePath conf) + >> pure s + Right (Test e1' e2') -> + when (lhs /= rhs) (print $ FailedTest e1 e2 lhs rhs) >> pure s + where + lhs = reduce e1' + rhs = reduce e2' + _ -> pure s + | otherwise + -> pure s + evalInstruction :: Instruction -> EnvState -> (EnvState -> IO EnvState) -> IO EnvState -evalInstruction (ContextualInstruction instr inp) s@(EnvState env@(Environment envDefs) conf cache) rec - = case instr of +evalInstruction (ContextualInstruction instr inp) s@(EnvState env conf _) rec = + case instr of Define i e sub -> do EnvState subEnv _ _ <- evalSubEnv sub s - ( res , env') <- pure $ evalDefine i e subEnv `runState` env + ( res , env') <- pure $ evalDefinition i e subEnv `runState` env case res of Left err -> print (ContextualError err $ Context inp $ _nicePath conf) >> pure s -- don't continue @@ -144,74 +228,6 @@ evalInstruction (ContextualInstruction instr inp) s@(EnvState env@(Environment e | _isRepl conf -> (putStrLn $ show i <> " = " <> show e) >> return s { _env = env' } | otherwise -> rec s { _env = env' } - Input path -> do - full <- fullPath path - if full `elem` _evalPaths conf - then - print - (ContextualError (ImportError path) (Context inp $ _nicePath conf) - ) - >> pure s - else if M.member path (_imported cache) - then - let (Environment env') = fromJust $ M.lookup path (_imported cache) - in rec s { _env = Environment $ M.union env' envDefs } - else do - EnvState (Environment env') _ cache' <- loadFile - full - (conf { _nicePath = path }) - cache -- TODO: Fix wrong `within` in import error - cache'' <- pure $ cache - { _imported = M.insert path (Environment env') - $ M.union (_imported cache) (_imported cache') - } - rec $ EnvState (Environment $ M.union env' envDefs) conf cache'' -- import => _isRepl = False - Import path namespace -> do -- TODO: Merge with Input (very similar) - full <- fullPath path - if full `elem` _evalPaths conf - then - print - (ContextualError (ImportError path) (Context inp $ _nicePath conf) - ) - >> pure s - else if M.member path (_imported cache) - then -- load from cache - let - (Environment env') = fromJust $ M.lookup path (_imported cache) - prefix | null namespace = takeBaseName path ++ "." - | namespace == "." = "" - | otherwise = namespace ++ "." - rewriteKeys "" = id - rewriteKeys p = M.mapKeys $ \f -> NamespacedFunction p f - rewriteFuns = - M.map $ \d -> d { _flags = (_flags d) { _isImported = True } } - filterImported = - M.filter $ \(EnvDef { _flags = f }) -> _isImported f == False - env'' = rewriteFuns $ rewriteKeys prefix $ filterImported env' - in - rec s { _env = Environment $ M.union env'' envDefs } - else do - EnvState (Environment env') _ cache' <- loadFile - full - (conf { _nicePath = path }) - cache -- TODO: Fix wrong `within` in import error - cache'' <- pure $ cache - { _imported = M.insert path (Environment env') - $ M.union (_imported cache) (_imported cache') - } - let - prefix | null namespace = takeBaseName path ++ "." - | namespace == "." = "" - | otherwise = namespace ++ "." - rewriteKeys "" = id - rewriteKeys p = M.mapKeys $ \f -> NamespacedFunction p f - rewriteFuns = - M.map $ \d -> d { _flags = (_flags d) { _isImported = True } } - filterImported = - M.filter $ \(EnvDef { _flags = f }) -> _isImported f == False - env'' <- pure $ rewriteFuns $ rewriteKeys prefix $ filterImported - env' - rec $ EnvState (Environment $ M.union env'' envDefs) conf cache'' -- import => _isRepl = False Evaluate e -> let (res, _) = evalExp e (Environment M.empty) `runState` env in putStrLn @@ -229,22 +245,12 @@ evalInstruction (ContextualInstruction instr inp) s@(EnvState env@(Environment e where reduced = reduce e' ) >> rec s - Test e1 e2 - | _evalTests conf - -> let (res, _) = evalTest e1 e2 (Environment M.empty) `runState` env - in - case res of - Left err -> - print (ContextualError err $ Context inp $ _nicePath conf) - >> pure s - Right (Test e1' e2') -> - when (lhs /= rhs) (print $ FailedTest e1 e2 lhs rhs) >> rec s - where - lhs = reduce e1' - rhs = reduce e2' - _ -> rec s - | otherwise - -> rec s + Commands cs -> yeet (pure s) cs >>= rec + where -- TODO: sus + yeet s' [] = s' + yeet s' (c : cs') = do + s'' <- s' + yeet (evalCommand inp s'' c) cs' _ -> rec s evalInstruction instr s rec = evalInstruction (ContextualInstruction instr "<unknown>") s rec @@ -278,7 +284,7 @@ evalFileConf path wr conv conf = do arg <- encodeStdin case evalMainFunc env arg of Nothing -> print - $ ContextualError (UndeclaredIdentifier entryFunction) (Context "" path) + $ ContextualError (UndefinedIdentifier entryFunction) (Context "" path) Just e -> wr $ conv e dumpFile :: String -> (a -> IO ()) -> (Expression -> a) -> IO () @@ -288,7 +294,7 @@ dumpFile path wr conv = do (EnvCache M.empty) case M.lookup entryFunction env of Nothing -> print - $ ContextualError (UndeclaredIdentifier entryFunction) (Context "" path) + $ ContextualError (UndefinedIdentifier entryFunction) (Context "" path) Just EnvDef { _exp = e } -> wr $ conv e evalFile :: String -> (a -> IO ()) -> (Expression -> a) -> IO () diff --git a/src/Helper.hs b/src/Helper.hs index 78b1f1c..5433dd0 100644 --- a/src/Helper.hs +++ b/src/Helper.hs @@ -35,13 +35,13 @@ printContext (Context inp path) = p $ lines inp errPrefix :: String errPrefix = "\ESC[41mERROR\ESC[0m " -data Error = SyntaxError String | UndeclaredIdentifier Identifier | InvalidIndex Int | FailedTest Expression Expression Expression Expression | ContextualError Error Context | ImportError String +data Error = SyntaxError String | UndefinedIdentifier Identifier | InvalidIndex Int | FailedTest Expression Expression Expression Expression | ContextualError Error Context | ImportError String instance Show Error where show (ContextualError err ctx) = show err <> "\n" <> (printContext ctx) show (SyntaxError err) = errPrefix <> "invalid syntax\n\ESC[45mnear\ESC[0m " <> err - show (UndeclaredIdentifier ident) = - errPrefix <> "undeclared identifier " <> show ident + show (UndefinedIdentifier ident) = + errPrefix <> "undefined identifier " <> show ident show (InvalidIndex err) = errPrefix <> "invalid index " <> show err show (FailedTest exp1 exp2 red1 red2) = errPrefix @@ -102,7 +102,9 @@ instance Show Identifier where show ident = "\ESC[95m" <> functionName ident <> "\ESC[0m" data Expression = Bruijn Int | Function Identifier | Abstraction Expression | Application Expression Expression | Infix Expression Identifier Expression | Prefix Identifier Expression deriving (Ord, Eq) -data Instruction = Define Identifier Expression [Instruction] | Evaluate Expression | Comment | Input String | Import String String | Test Expression Expression | ContextualInstruction Instruction String +data Command = Input String | Import String String | Test Expression Expression + deriving (Show) +data Instruction = Define Identifier Expression [Instruction] | Evaluate Expression | Comment | Commands [Command] | ContextualInstruction Instruction String deriving (Show) instance Show Expression where show (Bruijn x ) = "\ESC[91m" <> show x <> "\ESC[0m" diff --git a/src/Parser.hs b/src/Parser.hs index 2e929e1..d60cddb 100644 --- a/src/Parser.hs +++ b/src/Parser.hs @@ -188,36 +188,26 @@ parseComment = do _ <- some $ noneOf "\r\n" return () -parseImport :: Parser Instruction +parseImport :: Parser Command parseImport = do - inp <- getInput _ <- string ":import " <?> "import instruction" path <- importPath ns <- (try $ (sc *> (namespace <|> string "."))) <|> (eof >> return "") - pure $ ContextualInstruction (Import (path ++ ".bruijn") ns) inp + pure (Import (path ++ ".bruijn") ns) -parseInput :: Parser Instruction +parseInput :: Parser Command parseInput = do - inp <- getInput _ <- string ":input " <?> "input instruction" path <- importPath - pure $ ContextualInstruction (Input $ path ++ ".bruijn") inp + pure (Input $ path ++ ".bruijn") -parsePrint :: Parser Instruction -parsePrint = do - inp <- getInput - _ <- string ":print " <?> "print instruction" - e <- parseExpression - pure $ ContextualInstruction (Evaluate e) inp - -parseTest :: Parser Instruction +parseTest :: Parser Command parseTest = do - inp <- getInput - _ <- string ":test " <?> "test" - e1 <- (parens parseExpression <?> "first expression") + _ <- string ":test " <?> "test" + e1 <- (parens parseExpression <?> "first expression") sc e2 <- (parens parseExpression <?> "second expression") - pure $ ContextualInstruction (Test e1 e2) inp + pure (Test e1 e2) parseCommentBlock :: Parser Instruction parseCommentBlock = do @@ -226,24 +216,28 @@ parseCommentBlock = do eof return $ ContextualInstruction Comment inp --- TODO: Add comment/test [Instruction] parser and combine with (this) def block? +parseCommandBlock :: Parser Instruction +parseCommandBlock = do + inp <- getInput + commands <- + sepEndBy1 parseTest newline + <|> sepEndBy1 parseInput newline + <|> sepEndBy1 parseImport newline + return $ ContextualInstruction (Commands commands) inp + parseDefBlock :: Int -> Parser Instruction parseDefBlock lvl = (sepEndBy parseComment newline) *> string (replicate lvl '\t') - *> ( try (parseDefine lvl) - <|> try parsePrint - <|> try parseImport - <|> try parseInput - <|> try parseTest - ) + *> (try (parseDefine lvl)) parseBlock :: Int -> Parser Instruction -parseBlock lvl = try parseCommentBlock <|> parseDefBlock lvl +parseBlock lvl = + try parseCommentBlock <|> try (parseDefBlock lvl) <|> parseCommandBlock parseReplLine :: Parser Instruction parseReplLine = - try parseReplDefine - <|> try parseImport - <|> try parseTest + try parseReplDefine -- TODO: This is kinda hacky + <|> ((Commands . (: [])) <$> (try parseImport)) + <|> ((Commands . (: [])) <$> (try parseTest)) <|> try parseEvaluate diff --git a/std/List.bruijn b/std/List.bruijn index 891dc7c..7673456 100644 --- a/std/List.bruijn +++ b/std/List.bruijn @@ -18,7 +18,6 @@ empty? [0 [[[false]]] true] <>?( empty? :test (<>?empty) (true) -:test (<>?(cons (+2) empty)) (false) # prepends an element to a list cons P.pair @@ -26,6 +25,7 @@ cons P.pair (:) cons :test ((+1) : ((+2) : empty)) (P.pair (+1) (P.pair (+2) empty)) +:test (<>?((+2) : empty)) (false) # returns the head of a list or empty head P.fst @@ -203,6 +203,7 @@ concat foldr append empty # TODO: ? # :test (concat ((((+1) : ((+2) : empty)) : ((+3) : ((+4) : empty))) : empty)) ((+1) : ((+2) : ((+3) : ((+4) : empty)))) + :test (concat ("a" : ("b" : empty))) ("ab") # maps a function returning list of list and concatenates @@ -336,6 +337,6 @@ iterate z [[[rec]]] rec 0 : (2 1 (1 0)) :test (take (+5) (iterate inc (+0))) (((+0) : ((+1) : ((+2) : ((+3) : ((+4) : empty)))))) -:test (take (+2) (iterate dec (+5))) (((+5) : ((+4) : empty))) -:test (take (+5) (iterate i (+4))) (repeat (+5) (+4)) +:test (take (+2) (iterate sdec (+5))) (((+5) : ((+4) : empty))) +:test (take (+5) (iterate i (+4))) (take (+5) (repeat (+4))) :test (take (+0) (iterate inc (+0))) (empty) diff --git a/std/String.bruijn b/std/String.bruijn index 4c872a8..20634c7 100644 --- a/std/String.bruijn +++ b/std/String.bruijn @@ -12,6 +12,14 @@ eq? eq? B.eq? :test ("ab" =? "ab") (true) :test ("ab" =? "aa") (false) +# returns true if character is part of a string +in? in? B.eq? + +∈ \in? + +:test (∈ 'b' "ab") (true) +:test (∈ 'c' "ab") (false) + # splits string by newline character lines Z [[rec]] rec <>?(~broken) (^broken : empty) (^broken : (1 ~(~broken))) |