X-Git-Url: https://git.martlubbers.net/?a=blobdiff_plain;f=src%2Fparse.icl;h=042ec474e2270fa34c0d127c2f9793e82b4f4fcb;hb=3d1c57710eb0b86f13df392f03131157aec22c21;hp=0860819c20748b7d5a3b3a523691250172818c6f;hpb=6e527e30012f8809594452cb9559b301b4a8afc6;p=cc1516.git diff --git a/src/parse.icl b/src/parse.icl index 0860819..042ec47 100644 --- a/src/parse.icl +++ b/src/parse.icl @@ -24,13 +24,14 @@ parser (Right r) = case runParser parseProgram r of (Left e, _) = Left $ toString e parseProgram :: Parser Token AST -parseProgram = liftM2 AST (many parseVarDecl) (some parseFunDecl) +parseProgram = liftM2 AST (many parseVarDecl) (some parseFunDecl) +// <* satTok EndOfFileToken parseFunDecl :: Parser Token FunDecl parseFunDecl = liftM5 FunDecl (parseIdent <* satTok BraceOpenToken) (parseSepList CommaToken parseIdent <* satTok BraceCloseToken) - (parseFunType <* satTok CBraceOpenToken) + (optional parseFunType <* satTok CBraceOpenToken) (many parseVarDecl) (many parseStmt <* satTok CBraceCloseToken) @@ -52,10 +53,11 @@ parseStmt = parseIfStmt <|> parseWhileStmt <|> parseIfStmt :: Parser Token Stmt parseIfStmt = liftM3 IfStmt - (satTok IfToken *> parseBBraces parseExpr) - (parseBlock <|> parseOneLine) - (liftM (fromMaybe []) - (optional (satTok ElseToken *> (parseBlock<|> parseOneLine)))) + (satTok IfToken *> parseBBraces parseExpr) + (parseBlock <|> parseOneLine) + (liftM (fromMaybe []) + (optional (satTok ElseToken *> (parseBlock<|> parseOneLine)))) + parseWhileStmt :: Parser Token Stmt parseWhileStmt = satTok WhileToken *> @@ -69,7 +71,7 @@ parseStmt = parseIfStmt <|> parseWhileStmt <|> parseOneLine = liftM pure parseStmt parseFunType :: Parser Token FunType -parseFunType = satTok DoubleColonToken *> +parseFunType = satTok DoubleColonToken *> (parseInOutType <|> (liftM (FunType []) parseVoidOrType)) where parseInOutType :: Parser Token FunType @@ -78,7 +80,7 @@ parseFunType = satTok DoubleColonToken *> parseVoidOrType :: Parser Token (Maybe Type) parseVoidOrType = (satTok VoidToken *> pure Nothing) <|> - (liftM Just parseType) + (liftM Just parseType) <|> pure Nothing parseVarDecl :: Parser Token VarDecl parseVarDecl = liftM3 VarDecl @@ -149,8 +151,7 @@ parseVarDef = liftM2 VarDef (parseIdent >>= \i.if (i == "snd") (pure FieldSnd) empty)))) parseOp1 :: Parser Token Op1 -parseOp1 = trans1 DashToken UnMinus <|> - trans1 ExclamationToken UnNegation +parseOp1 = trans1 DashToken UnMinus <|> trans1 ExclamationToken UnNegation parseBBraces :: (Parser Token a) -> Parser Token a parseBBraces p = satTok BraceOpenToken *> p <* satTok BraceCloseToken @@ -167,7 +168,7 @@ parseTuple p = satTok BraceOpenToken *> <* satTok BraceCloseToken trans2 :: TokenValue (TokenValue -> a) -> Parser Token a -trans2 t f = satTok t >>= \(_, r).pure (f r) +trans2 t f = liftM (f o thd3) $ satTok t trans1 :: TokenValue a -> Parser Token a trans1 t r = trans2 t $ const r @@ -175,16 +176,18 @@ trans1 t r = trans2 t $ const r derive gPrint TokenValue derive gEq TokenValue satTok :: TokenValue -> Parser Token Token -satTok t = top >>= \tok=:(pos, tv) -> if (eq t tok) (return tok) (fail (printToString t, pos)) +satTok t = top >>= \tok=:(pos1, pos2, tv) -> if (eq t tok) + (return tok) + (fail (printToString tv+++printToString t, pos1)) where - eq (IdentToken _) (_, IdentToken _) = True - eq (NumberToken _) (_, NumberToken _) = True - eq (CharToken _) (_, CharToken _) = True - eq x (_, y) = gEq {|*|} x y + eq (IdentToken _) (_, _, IdentToken _) = True + eq (NumberToken _) (_, _, NumberToken _) = True + eq (CharToken _) (_, _, CharToken _) = True + eq x (_, _, y) = gEq {|*|} x y parseSepList :: TokenValue (Parser Token a) -> Parser Token [a] parseSepList sep p = - (some (p <* satTok sep) >>= \es->p >>= \e.pure $ reverse [e:es]) <|> + (liftM2 (\es->(\e->reverse [e:es])) (some (p <* satTok sep)) p) <|> (liftM pure p) <|> pure empty parseIdent :: Parser Token String @@ -203,9 +206,9 @@ printersperse i j = intercalate [i] (map print j) instance print FunDecl where print (FunDecl i as t vs ss) = ["\n", i, " (":printersperse "," as] ++ - [") :: ":print t] ++ - ["{":printersperse "\n\t" vs] ++ - ["\n":printStatements ss 1] ++ ["}"] + [")"] ++ maybe [] (\tt->[" :: ":print tt]) t ++ + ["{\n\t":printersperse "\n\t" vs] ++ + ["\n":printStatements ss 1] ++ ["}\n"] printStatements :: [Stmt] Int -> [String] printStatements [] i = [] @@ -222,7 +225,7 @@ printStatements [s:ss] i = (case s of ) ++ printStatements ss i where printCodeBlock :: [Stmt] Int -> [String] - printCodeBlock [] _ = ["{}"] + printCodeBlock [] _ = ["{}\n"] printCodeBlock [x] i = ["\n":printStatements [x] (i+1)] printCodeBlock x i = ["{\n":printStatements x (i+1)] ++ indent i ["}\n"]