aboutsummaryrefslogtreecommitdiff
path: root/parser/CC/Parser.hs
blob: 2d2c4b7a864cd463ab9e68bc78711b6491143292 (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
module CC.Parser(runPass, parseProgram) where

import Control.Monad
import Text.Parsec hiding (SourcePos, getPosition, token)
import qualified Text.Parsec

import CC.AST.Source
import CC.Context
import CC.Pretty


type Parser a = Parsec String () a

runPass :: Context -> RawString -> Either (PrettyShow ParseError) Program
runPass (Context path _) (RawString src) = fmapLeft PrettyShow (parseProgram path src)
  where fmapLeft f (Left x) = Left (f x)
        fmapLeft _ (Right x) = Right x

parseProgram :: FilePath -> String -> Either ParseError Program
parseProgram fname src = parse pProgram fname src

pProgram :: Parser Program
pProgram = do
    prog <- Program <$> many pDecl
    emptyLines
    eof
    return prog

pDecl :: Parser Decl
pDecl = Def <$> pDef

pDef :: Parser Def
pDef = do
    func <- try $ do
        emptyLines
        name <- pName0 <?> "declaration head name"
        return name
    mtyp <- optionMaybe $ do
        symbol "::"
        typ <- pType
        whitespace >> void newline
        emptyLines
        func' <- fst <$> pName0
        guard (fst func == func')
        return typ
    args <- many pName
    symbol "="
    expr <- pExpr
    return (Function mtyp func args expr)

pType :: Parser Type
pType = chainr1 pTypeAtom (symbol "->" >> return TFun)

pTypeAtom :: Parser Type
pTypeAtom = (wordToken "Int" >> return TInt) <|> pParenType

pParenType :: Parser Type
pParenType = do
    token "("
    tys <- pType `sepBy` token ","
    token ")"
    case tys of
        [ty] -> return ty
        _ -> return (TTup tys)

pExpr :: Parser Expr
pExpr = label (pLam <|> pLet <|> pCall) "expression"
  where
    pCall = do
        atoms <- many1 pExprAtom
        annot <- optionMaybe (do symbol "::"
                                 p1 <- getPosition
                                 ty <- pType
                                 p2 <- getPosition
                                 return (ty, SourceRange p1 p2))
        let call = foldl1 (\a b -> Call (mergeRange (range a) (range b)) a b) atoms
        case annot of
            Just (ty, sr) -> return (Annot (mergeRange (range call) sr) call ty)
            Nothing -> return call

    pLam = do
        p1 <- try $ do
            whitespace
            p <- getPosition
            void (char '\\')
            return p
        names <- many1 pName
        symbol "->"
        body <- pExpr
        p2 <- getPosition
        return (Lam (SourceRange p1 p2) names body)

    pLet = do
        p1 <- try $ do
            whitespace
            p <- getPosition
            void (string "let")
            return p
        afterKeyword p1
      where
        afterKeyword p1 = do
            whitespace1
            lhs <- pName0
            symbol "="
            rhs <- pExpr
            let fullRange rest = mergeRange (SourceRange p1 p1) (range rest)
            choice [ do p1' <- try $ do
                            whitespace
                            p1' <- getPosition
                            void (string "let")
                            return p1'
                        rest <- afterKeyword p1'
                        return (Let (fullRange rest) lhs rhs rest)
                   , do symbol "in"
                        body <- pExpr
                        return (Let (fullRange body) lhs rhs body) ]

pExprAtom :: Parser Expr
pExprAtom =
    choice [ uncurry (flip Int) <$> pInt
           , uncurry (flip Var) <$> pName
           , pParenExpr ]

pParenExpr :: Parser Expr
pParenExpr = do
    p1 <- getPosition
    token "("
    exprs <- pExpr `sepBy` token ","
    token ")"
    p2 <- getPosition
    case exprs of
        [expr] -> return expr
        _ -> return (Tup (SourceRange p1 p2) exprs)

pInt :: Parser (Int, SourceRange)
pInt = try (whitespace >> pInt0)
  where
    pInt0 = do
        p1 <- getPosition
        num <- read <$> many1 digit
        p2 <- getPosition
        return (num, SourceRange p1 p2)

pName0 :: Parser (Name, SourceRange)
pName0 = do
    p1 <- getPosition
    s <- try $ do
        c <- pWordFirstChar
        cs <- many pWordMidChar
        let s = c : cs
        guard (s `notElem` ["let", "in"])
        return s
    p2 <- getPosition
    notFollowedBy pWordMidChar
    return (s, SourceRange p1 p2)

pWordFirstChar :: Parser Char
pWordFirstChar = letter <|> oneOf "_$#!"

pWordMidChar :: Parser Char
pWordMidChar = alphaNum <|> oneOf "_$#!"

pName :: Parser (Name, SourceRange)
pName = try (whitespace >> pName0)

symbol :: String -> Parser ()
symbol s = token s >> (eof <|> void space <|> void (oneOf "(){}[]"))

wordToken :: String -> Parser ()
wordToken s = token s >> notFollowedBy pWordMidChar

token :: String -> Parser ()
token s = try (whitespace >> void (string s))

emptyLines :: Parser ()
emptyLines = (try (whitespace >> newline) >> emptyLines) <|> try (whitespace >> eof) <|> return ()

whitespace, whitespace1 :: Parser ()
whitespace  = void (many  (void (char ' ') <|> void (try (string "\n "))))
whitespace1 = void (many1 (void (char ' ') <|> void (try (string "\n "))))

getPosition :: Parser SourcePos
getPosition = do
    pos <- Text.Parsec.getPosition
    return (SourcePos (sourceLine pos - 1) (sourceColumn pos - 1))