summaryrefslogtreecommitdiff
path: root/src/Parser.hs
blob: fcab06027b463b63240ea48aa39cf42f1675f7ec (plain)
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
module Parser (parseProgram) where

import Control.Monad
import Data.Char
import Data.List (foldl')
import Text.Parsec hiding (token)

import AST


type Parser = Parsec String ()

parseProgram :: String -> String -> Either ParseError [Definition]
parseProgram fname source = parse pProgram fname source

pProgram :: Parser [Definition]
pProgram = do
  whitespaceTo0
  choice
    [eof >> return []
    ,(:) <$> pDef <*> pProgram]

-- | Assumes column 0
pDef :: Parser Definition
pDef = do
  name <- pName
  whitespace
  token ":"
  whitespace
  typ <- pTerm 0
  whitespaceTo0
  name2 <- pName
  when (name /= name2) $
    fail $ "Definition of '" ++ name ++ "' followed by definition for '" ++ name2 ++ "'"
  whitespace
  token "="
  whitespace
  rhs <- pTerm 0
  return (Definition name (rhs :| typ))

-- operator precedences:
--   0 _:_
--   1 (_ : _) -> _
--   2 _,_

pTerm :: Int -> Parser Term
pTerm p | p <= 0 = do
  e1 <- pTerm 1
  whitespace
  choice
    [do token ":"
        whitespace
        e2 <- pTerm 1
        return (TAnnot (e1 :| e2))
    ,return e1]

pTerm 1 = do
  e1 <- pTerm 2
  whitespace
  choice
    [do (token "->" <|> token "→")
        (x :| ty) <- case e1 of
          TAnnot (TVar x :| ty) -> return (x :| ty)
          _ -> fail $ "Expected (x : type) as left-hand side of (->)"
        whitespace
        e2 <- pTerm 1
        return (TPi x ty e2)
    ,return e1]

pTerm 2 = do
  e1 <- pTerm 3
  whitespace
  choice
    [do token ","
        whitespace
        e2 <- pTerm 2
        return (TPair e1 e2)
    ,return e1]

pTerm _ = pTermEAtom

pTermEAtom :: Parser Term
pTermEAtom = pLambda <|> pSpecialApp <|> pApp

pLambda :: Parser Term
pLambda = do
  void (char '\\') <|> token "λ"
  whitespace
  _ <- char '('
  whitespace
  x <- pName
  whitespace
  token ":"
  whitespace
  ty <- pTerm 0
  whitespace
  _ <- char ')'
  whitespace
  token "->"
  whitespace
  rhs <- pTerm 0
  return (TLam x ty rhs)

pSpecialApp :: Parser Term
pSpecialApp = pSet <|> pSetw <|> pSigma
  where
    pSet :: Parser Term
    pSet = do
      token "Set"
      whitespace
      e <- pTermEAtom
      return (TSet e)

    pSetw :: Parser Term
    pSetw = do
      token "Setw"
      whitespace
      n <- read <$> many1 digit
      return (TSetw n)

    pSigma :: Parser Term
    pSigma = do
      token "Sigma"
      whitespace
      _ <- char '('
      whitespace
      x <- pName
      whitespace
      token ":"
      whitespace
      ty <- pTerm 0
      whitespace
      _ <- char ')'
      whitespace
      rhs <- pTermEAtom
      return (TSigma x ty rhs)

pApp :: Parser Term
pApp = do
  e1 <- pAtom
  args <- many (try (whitespace >> pAtom))
  return (foldl' TApp e1 args)

pAtom :: Parser Term
pAtom = choice
  [do _ <- char '('
      whitespace
      e <- pTerm 0
      whitespace
      _ <- char ')'
      return e
  ,TVar <$> pName]

-- TODO TPair, TSigma ("%"). The rest are environment entries.

pName :: Parser Name
pName = do
  name <- many1 pNameChar
  guard (name `notElem` keywords)
  guard (head name /= '\\')  -- lambda syntax
  return name
  where
    keywords = ["=", "->", "→", ":", "?", "\\", "λ", "∀", "..", "..."
               ,"forall", "data", "import", "in", "let"
               ,"Sigma", ","  -- temporary
               ]

pNameChar :: Parser Char
pNameChar = satisfy (\c -> not (isSpace c) && c `notElem` ".;{}()@\"")

inlineWhite :: Parser ()
inlineWhite = do
  skipMany inlineSpace
  choice
    [inlineComment
    -- TODO: nested {- -} comments
    ,return ()]

inlineComment :: Parser ()
inlineComment = token "--" >> manyTill anyChar (lookAhead newline) >> return ()

-- | Skips to the furthest point from here that can be reached without
-- consuming any tokens, and without ending on column 0.
whitespace :: Parser ()
whitespace = do
  inlineWhite
  optional $ try $
    many newline >> (inlineSpace <|> inlineComment) >> whitespace

inlineSpace :: Parser ()
inlineSpace = void (satisfy (\c -> isSpace c && c /= '\n')) <?> "inline whitespace"

-- | Skips as much whitespace as possible, and throws an error if that doesn't
-- leave us on column 0.
whitespaceTo0 :: Parser ()
whitespaceTo0 = do
  inlineWhite
  choice
    [eof
    ,newline >> whitespaceTo0
    ,do pos <- getPosition
        when (sourceColumn pos /= 1) $
          unexpected "indented code"]

token :: String -> Parser ()
token s = try $ string s >> (eof <|> void (lookAhead (satisfy (\c -> isSpace c || c `elem` ".;{}()@\""))))