-
Notifications
You must be signed in to change notification settings - Fork 1
/
Parser.hs
222 lines (159 loc) · 4.48 KB
/
Parser.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
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
{-|
Module : Parser
Description : Monadic Parser Combinators for the untyped lambda calculus in Haskell.
Copyright : (c) Luke Geeson, 2018
License : GPL-3
Maintainer : mail@lukegeeson.com
Stability : stable
Portability : POSIX
The "Parser" module provides the monadic parser combinators, grammars, and top-level functions needed to parse a human friendly (read whiteboard) version of SKI.
-}
module Parser where
-- SKI imports.
import qualified SKI
-- Tool Imports.
import qualified Control.Monad as M (liftM, ap)
import qualified Data.Char as C
{-
Implementation based on ideas in Monadic Parser Combinators paper
http://www.cs.nott.ac.uk/~pszgmh/monparsing.pdf
-}
-- | Parser type takes input string and returns a list of possible parses.
newtype Parser a = Parser (String -> [(a, String)])
-- | Necessary AMP additions for Parser instance.
instance Functor Parser where
fmap = M.liftM
-- | Necessary AMP additions for Parser instance.
instance Applicative Parser where
pure a = Parser (\cs -> [(a,cs)])
(<*>) = M.ap
-- | Monad instance, generators use the first parser then apply f to the result
instance Monad Parser where
return = pure
p >>= f = Parser (\cs -> concat [parse (f a) cs' | (a,cs') <- parse p cs])
-- | Parser deconstructor.
parse :: Parser a -> String -> [(a, String)]
parse (Parser p) = p
-- | Item takes a string and splits on the first char or fails
item :: Parser Char
item = let split cs = case cs of
"" -> []
(c:cs) -> [(c,cs)]
in Parser split
-- | Combines the results of 2 parsers on an input string
-- shortcircuits on the first result returned or fails
(+++) :: Parser a -> Parser a -> Parser a
p +++ q = let apply cs = case parse p cs ++ parse q cs of
[] -> []
(x:_) -> [x]
in Parser apply
-- | Failure parser.
zerop = Parser (const [])
-- | Parses an element and returns if they satisfy a predicate.
sat :: (Char -> Bool) -> Parser Char
sat p = do
c <- item
if p c
then return c
else zerop
-- | Parses chars only.
char :: Char -> Parser Char
char c = sat (c ==)
-- | Parses a string of chars.
string :: String -> Parser String
string = mapM char
-- | Parses 0 or more elements.
many :: Parser a -> Parser [a]
many p = many1 p +++ return []
-- | Parses 1 or more elements.
many1 :: Parser a -> Parser [a]
many1 p = do
a <- p
as <- many p
return (a:as)
-- | Parses 0 or more whitespace.
space :: Parser String
space = many (sat C.isSpace)
-- | Parsers 1 or more whitespace.
space1 :: Parser String
space1 = many1 (sat C.isSpace)
-- | Trims whitespace between an expression.
spaces :: Parser a -> Parser a
spaces p = do
space
x <- p
space
return x
-- | Parses a single string.
symb :: String -> Parser String
symb = string
-- | Apply a parser to a string.
apply :: Parser a -> String -> [(a,String)]
apply = parse
-- | Left recursion.
chainl1 :: Parser a -> Parser (a -> a -> a) -> Parser a
p `chainl1` op = let rest a = (do f <- op
b <- p
rest (f a b)) +++ return a
in do a <- p
rest a
-- | set of reserved words for SKI
keywords :: [String]
keywords = ["let", "="]
-- | Parser 1 or more chars (a string).
str :: Parser String
str = do
s <- many1 $ sat C.isLower
if s `elem` keywords
then zerop
else return s
-- | Parses away brackets as you'd expect.
bracket :: Parser a -> Parser a
bracket p = do
symb "("
x <- p
symb ")"
return x
-- | Vars are strings packaged up.
var :: Parser SKI.SKTerm
var = SKI.Var <$> str
-- | Parser for S terms
s :: Parser SKI.SKTerm
s = do
char 'S'
return SKI.S
-- | Parser for K terms
k :: Parser SKI.SKTerm
k = do
char 'K'
return SKI.K
-- | Parser for I terms
i :: Parser SKI.SKTerm
i = do
char 'I'
return SKI.I
-- | App parses application terms, with one or more spaces in between terms.
app :: Parser SKI.SKTerm
app = chainl1 expr $ do
space1
return SKI.App
-- | Parser for let expressions
pLet = do
space
symb "let"
space1
v <- str
spaces $ symb "="
t <- term
return (v,t)
-- | Parser for regular terms.
pTerm = do
t <- term
return ("", t)
-- | Expression follows CFG form with bracketing convention.
expr = bracket term +++ var +++ s +++ k +++ i
-- | Top-level of CFG Grammar.
term = app
-- | Identifies key words.
identifier :: String -> Parser Char
identifier xs = sat (`elem` xs)