-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathParser.hs
36 lines (21 loc) · 970 Bytes
/
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
{-# LANGUAGE UnicodeSyntax #-}
module HLisp.Parser ( parse ) where
import HLisp.Types
import Text.Parsec hiding ( parse )
import Prelude.Unicode
import Control.Applicative hiding ( (<|>), many )
infixl 8 ∘:
(f ∘: g) x y = f (g x y)
(~|~) = (() <$) ∘: (<|>)
strLit = StrT <$> (char '"' *> many (noneOf "\"") <* char '"')
chrLit = ChrT <$> (string "#\\" *> anyChar)
intLit = IntT ∘ read ∘: (:) <$> option ' ' (char '-') <*> many1 digit
<* lookAhead (space ~|~ oneOf "()" ~|~ eof)
symbol = SymT <$> many1 (noneOf "() \n\t\r")
atom = strLit <|> chrLit <|> try intLit <|> symbol
expr = LisT <$> (char '(' *> spaces *> (form `sepEndBy` spaces) <* char ')')
quoted = LisT ∘ (SymT "quote" :) ∘ (:[]) <$> (char '\'' *> spaces *> form)
form = quoted <|> expr <|> atom
top = many (spaces *> form <* spaces)
parse ∷ String -> Either ParseError [T]
parse = runParser top () ""