-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathParse.hs
103 lines (80 loc) · 2.73 KB
/
Parse.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
module Parse where
import ParseLib
import Syntax
import Data.Char
parseProgFile file =
do contents <- readFile file
return (parseProg contents)
parseProg = parse prog
keywords :: [String]
keywords =
[ "case", "of", "let"
, "in", "emit", "emitInt"
, "if", "then", "else"
]
identifier :: Parser Char -> Parser String
identifier begin = token (guarded g (pure (:) <*> begin <*> many alphanum))
where g s = s `notElem` keywords
lowerIdent :: Parser String
lowerIdent = identifier lower
upperIdent :: Parser String
upperIdent = identifier upper
key :: String -> Parser String
key s = token $ \input ->
[(rest, a) | (rest, a) <- string s input
, null rest || not (isAlphaNum (head rest))]
prog :: Parser Prog
prog = block defn
block :: Parser a -> Parser [a]
block p = tok "{" |> seq <| tok "}"
where seq = seq' <| (tok ";" <|> pure "")
seq' = pure (:) <*> p <*> many (tok ";" |> p)
defn :: Parser Decl
defn = pure Func <*> lowerIdent <*> many pat <*> tok "=" |> expr
expr :: Parser Exp
expr = pure App <*> expr' <*> many expr'
expr' :: Parser Exp
expr' = pure Case <*> (key "case" |> expr) <*> (key "of" |> block alt)
<|> pure Let <*> (key "let" |> block bind) <*> (key "in" |> expr)
<|> pure Var <*> lowerIdent
<|> pure Con <*> upperIdent
<|> pure Int <*> int
<|> pure Fun <*> prim
<|> pure prsApp <*> (tok "<" |> expr) <*> prsOp <*> (expr <| tok ">")
<|> ifte
<|> pure charList <*> token strLit
<|> pure oneChar <*> token charLit
<|> tok "(" |> expr <| tok ")"
prim :: Parser String
prim = tok "(+)" <|> tok "(-)" <|> tok "(==)" <|> tok "(/=)" <|> tok "(<=)"
<|> key "emit" <|> key "emitInt"
prsOp :: Parser String
prsOp = tok "+" <|> tok "-" <|> tok "==" <|> tok "/=" <|> tok "<="
prsApp :: Exp -> String -> Exp -> Exp
prsApp e1 op e2 = PRSApp ("(" ++ op ++ ")") [e1, e2]
pat :: Parser Pat
pat = pure Var <*> lowerIdent
<|> pure (\s -> App (Con s) []) <*> upperIdent
<|> tok "(" |> pat' <| tok ")"
pat' :: Parser Pat
pat' = pure Var <*> lowerIdent
<|> pure App <*> (pure Con <*> upperIdent) <*> many pat
bind :: Parser Binding
bind = pure (,) <*> (lowerIdent <| tok "=") <*> expr
alt :: Parser Alt
alt = pure (,) <*> (pat' <| tok "->" ) <*> expr
ifte :: Parser Exp
ifte = pure cond <*> (key "if" |> expr)
<*> (key "then" |> expr)
<*> (key "else" |> expr)
where
cond e1 e2 e3 = Case e1 [ (App (Con "True") [], e2)
, (App (Con "False") [], e3)
]
charList :: String -> Exp
charList s = charList' (read s)
where
charList' "" = Con "Nil"
charList' (c:cs) = App (Con "Cons") [Int (fromEnum c), charList' cs]
oneChar :: String -> Exp
oneChar s = Int (fromEnum (read s :: Char))