| FunStmt String [Expr]
| ReturnStmt (Maybe Expr)
-instance toString AST
-instance toString Type
instance toString Pos
-instance toString Op2
-instance == Op2
-instance toString FieldSelector
+instance toString Type
+instance toString AST
print BoolType = print "Bool"
print CharType = print "Char"
print VoidType = print "Void"
- print (t1 ->> t2) = print t1 ++ [" -> ":print t2]
+ print (t1 ->> t2) = ["(":print t1 ++ [" -> ":print t2]] ++ [")"]
instance print String where
print s = [s]
print FieldFst = print "fst"
instance print VarDef where
- print (VarDef i fs) = printersperse "." [i:flatten $ map print fs]
+ print (VarDef i fs) = printersperse "." [i:printersperse "" fs]
instance toString Op2 where
toString o = case o of
man: spl.1
-spl: spl.icl lex.icl lex.dcl parse.icl parse.dcl spl.prj sem.icl sem.dcl
+spl: spl.icl lex.icl lex.dcl parse.icl parse.dcl spl.prj sem.icl sem.dcl AST.icl AST.dcl
$(CPM) make
%.1: %
<Prog> ::= <FunDecl>+
<FunDecl> ::= <id> '(' <Type>* ')' ['::' <FunType] '{' <VarDecl>* <Stmt>+ '}'
<FunType> ::= <VoidType> ['->' <FunType>]
+ | '(' <FunType> ')'
<Stmt> ::= 'if' '(' <Expr> ')' '{' <Stmt>* '}' ['else' '{' <Stmt>* '}']
| 'while' '(' <Expr> ')' '{' <Stmt>* '}'
| <id> <FieldSels> '=' <Expr> ';'
parseFunType = satTok DoubleColonToken *> parseFT
where
parseFT :: Parser Token Type
- parseFT = ((->>) <$> parseType <* satTok ArrowToken <*> parseFT) <|> parseType
+ parseFT = (liftM2 (->>)
+ ((parseBBraces parseFT <|> parseType) <* satTok ArrowToken)
+ parseFT) <|> parseType
parseVarDecl :: Parser Token VarDecl
parseVarDecl = liftM4 VarDecl
parseFieldSelectors :: Parser Token [FieldSelector]
parseFieldSelectors = many (satTok DotToken *> (
- (parseIdent >>= (\i.if (i == "hd") (pure FieldHd) empty)) <|>
- (parseIdent >>= \i.if (i == "tl") (pure FieldTl) empty) <|>
- (parseIdent >>= \i.if (i == "fst") (pure FieldFst) empty) <|>
- (parseIdent >>= \i.if (i == "snd") (pure FieldSnd) empty)))
+ (parseIdent >>= \i.if (i == "hd") (pure FieldHd) empty) <|>
+ (parseIdent >>= \i.if (i == "tl") (pure FieldTl) empty) <|>
+ (parseIdent >>= \i.if (i == "fst") (pure FieldFst) empty) <|>
+ (parseIdent >>= \i.if (i == "snd") (pure FieldSnd) empty)))
parseOp1 :: Parser Token Op1
parseOp1 = trans1 DashToken UnMinus <|> trans1 ExclamationToken UnNegation
parseTuple :: (Parser Token a) -> Parser Token (a, a)
parseTuple p = satTok BraceOpenToken *>
- (liftM2 (\a->(\b->(a,b))) (p <* satTok CommaToken) p)
+ (liftM2 tuple (p <* satTok CommaToken) p)
<* satTok BraceCloseToken
trans :: TokenValue (TokenValue -> a) -> Parser Token (Pos, a)
variableStream = map toString [1..]
sem :: AST -> SemOutput
-sem (AST fd) = Right $ (AST fd, 'Map'.newMap)
+sem (AST fd) = Right (AST fd, 'Map'.newMap)
instance toString Scheme where
- toString (Forall x t) = concat ["Forall ": map ((+++) "\n") x] +++ toString t
+ toString (Forall x t) =
+ concat ["Forall ": map ((+++) "\n") x] +++ toString t
instance toString Gamma where
- toString mp = concat [concat [k, ": ", toString v, "\n"]\\(k, v)<-'Map'.toList mp]
+ toString mp =
+ concat [concat [k, ": ", toString v, "\n"]\\(k, v)<-'Map'.toList mp]
instance toString SemError where
toString se = "SemError: "