blob: 6fbfc106f6efc6d3f121b0441e9006b46100f8a7 (
plain) (
blame)
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
|
module Parser
( parseBlock
, parseReplLine
) where
import Control.Monad ( ap
, void
)
import Data.Functor.Identity
import Data.Void
import Helper
import Text.Megaparsec hiding ( parseTest )
import Text.Megaparsec.Char
import qualified Text.Megaparsec.Char.Lexer as L
type Parser = Parsec Void String
-- exactly one space
-- TODO: replace many scs with sc
sc :: Parser ()
sc = void $ char ' '
-- zero or more spaces
scs :: Parser ()
scs = void $ takeWhileP (Just "white space") (== ' ')
lexeme :: Parser a -> Parser a
lexeme = L.lexeme scs
symbol :: String -> Parser String
symbol = L.symbol scs
-- def identifier disallows the import prefix dots
defIdentifier :: Parser String
defIdentifier =
lexeme
((:) <$> (letterChar <|> char '_') <*> many
(alphaNumChar <|> oneOf "?!'_-")
)
<?> "defining identifier"
-- TODO: write as extension to defIdentifier
identifier :: Parser String
identifier =
lexeme
((:) <$> (letterChar <|> char '_') <*> many
(alphaNumChar <|> oneOf "?!'_-.")
)
<?> "identifier"
namespace :: Parser String
namespace =
lexeme ((:) <$> upperChar <*> many letterChar)
<|> string "."
<|> (scs >> return "")
<?> "namespace"
parens :: Parser a -> Parser a
parens = between (symbol "(") (symbol ")")
almostAnything :: Parser String
almostAnything =
some $ oneOf ".`#~@$%^&*_+-=|;',/?[]<>(){} " <|> letterChar <|> digitChar
importPath :: Parser String
importPath = some $ oneOf "./_+-" <|> letterChar <|> digitChar
parseAbstraction :: Parser Expression
parseAbstraction = do
symbol "[" <?> "opening abstraction"
exp <- parseExpression
symbol "]" <?> "closing abstraction"
pure $ Abstraction exp
parseApplication :: Parser Expression
parseApplication = do
s <- sepBy1 parseSingleton scs
pure $ foldl1 Application s
parseBruijn :: Parser Expression
parseBruijn = do
idx <- digitChar
scs
pure $ Bruijn $ (read . pure) idx
parseNumeral :: Parser Expression
parseNumeral = do
num <- number <?> "signed number"
scs
pure $ decimalToTernary num
where
sign :: Parser (Integer -> Integer)
sign = (char '-' >> return negate) <|> (char '+' >> return id)
nat :: Parser Integer
nat = read <$> some digitChar
number :: Parser Integer
number = ap sign nat
parseVariable :: Parser Expression
parseVariable = do
var <- identifier
scs
pure $ Variable var
parseSingleton :: Parser Expression
parseSingleton =
parseBruijn
<|> parseNumeral
<|> parseAbstraction
<|> (parens parseApplication <?> "enclosed application")
<|> parseVariable
parseExpression :: Parser Expression
parseExpression = do
scs
expr <- parseApplication <|> parseSingleton
scs
pure expr <?> "expression"
parseEvaluate :: Parser Instruction
parseEvaluate = Evaluate <$> parseExpression
parseDefine :: Int -> Parser Instruction
parseDefine lvl = do
var <- defIdentifier
scs
exp <- parseExpression
-- TODO: Fix >1 sub-defs
subs <-
(try $ newline *> (sepEndBy (parseBlock (lvl + 1)) newline))
<|> (try eof >> return [])
pure $ Define var exp subs
parseReplDefine :: Parser Instruction
parseReplDefine = do
var <- defIdentifier
scs
symbol "="
scs
exp <- parseExpression
pure $ Define var exp []
parseComment :: Parser Instruction
parseComment = string "#" >> Comment <$> almostAnything <?> "comment"
parseImport :: Parser Instruction
parseImport = do
string ":import " <?> "import"
scs
path <- importPath
scs
ns <- namespace
scs
pure $ Import (path ++ ".bruijn") ns
parsePrint :: Parser Instruction
parsePrint = do
string ":print " <?> "print"
scs
exp <- parseExpression
scs
pure $ Evaluate exp
parseTest :: Parser Instruction
parseTest = do
string ":test " <?> "test"
exp1 <- parseExpression
scs
symbol "="
scs
exp2 <- parseExpression
pure $ Test exp1 exp2
-- TODO: Add comment/test [Instruction] parser and combine with (this) def block
parseBlock :: Int -> Parser Instruction
parseBlock lvl =
string (replicate lvl '\t')
*> try (parseDefine lvl)
<|> try parseComment
<|> try parsePrint
<|> try parseImport
<|> try parseTest
parseReplLine :: Parser Instruction
parseReplLine =
try parseReplDefine
<|> try parseComment
<|> try parseEvaluate
<|> try parseImport
<|> try parseTest
|