-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy path10-static-types.hs
290 lines (241 loc) · 8.62 KB
/
10-static-types.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
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
{-# LANGUAGE GADTs #-}
import Prelude
import Parsing hiding ((<$>), (<$), (<*>), (<*), (*>))
import qualified Data.Map as M
data Arith where
Lit :: Integer -> Arith
Bin :: Op -> Arith -> Arith -> Arith
Var :: String -> Arith
Let :: String -> Arith -> Arith -> Arith
BFalse :: Arith
BTrue :: Arith
If :: Arith -> Arith -> Arith -> Arith
deriving (Show)
data Op where
Plus :: Op
Minus :: Op
Times :: Op
Div :: Op
Less :: Op
Eq :: Op
deriving (Show, Eq)
data FullArith where
FLit :: Integer -> FullArith
FUn :: FOp -> FullArith -> FullArith
FBin :: FOp -> FullArith -> FullArith -> FullArith
FVar :: String -> FullArith
FLet :: String -> FullArith -> FullArith -> FullArith
FFalse :: FullArith
FTrue :: FullArith
FIf :: FullArith -> FullArith -> FullArith -> FullArith
deriving (Show)
data FOp where
ArOp :: Op -> FOp
Le :: FOp
Ne :: FOp
Gt :: FOp
Ge :: FOp
Not :: FOp
And :: FOp
Or :: FOp
deriving (Show, Eq)
data Type where
TBool :: Type
TInteger :: Type
deriving (Show, Eq)
type Env = M.Map String Integer
type Ctx = M.Map String Type
data TypeError where
UndefinedVar :: String -> TypeError
-- expr, expected type, actual type
TypeMismatch :: Arith -> Type -> Type -> TypeError
-- if expr, type then, type else
IfBranchesMismatch :: Arith -> Type -> Type -> TypeError
deriving (Show)
showTypeError :: TypeError -> String
showTypeError (UndefinedVar v) = "Undefined variable '" ++ v ++ "'"
showTypeError (TypeMismatch e t1 t2) =
"Type mismatch: expected " ++ show t1 ++
" but got " ++ show t2 ++ " in expression " ++ showArith e
showTypeError (IfBranchesMismatch e t1 t2) =
"Branches have different types: " ++ show t1 ++
" and " ++ show t2 ++ " in expression " ++ showArith e
data InterpError where
DivisonByZero :: InterpError
deriving (Show)
showInterpError :: InterpError -> String
showInterpError (DivisonByZero) = "Division by zero"
showOp :: Op -> String
showOp Plus = "+"
showOp Minus = "-"
showOp Times = "*"
showOp Div = "/"
showOp Less = "<"
showOp Eq = "=="
showArith :: Arith -> String
showArith (Lit i) = show i
showArith BTrue = "True"
showArith BFalse = "False"
showArith (Bin op e1 e2) = (showArith e1) ++ showOp op ++ (showArith e2)
showArith (Var x) = x
showArith (Let v e1 e2) = "let " ++ v ++ " = " ++ showArith e1 ++ " in " ++ (showArith e2)
showArith (If cond eThen eElse) =
"if " ++ showArith cond ++
" then " ++ showArith eThen ++
" else " ++ showArith eElse
bopType :: Op -> (Type, Type, Type)
bopType Plus = (TInteger, TInteger, TInteger)
bopType Minus = (TInteger, TInteger, TInteger)
bopType Times = (TInteger, TInteger, TInteger)
bopType Div = (TInteger, TInteger, TInteger)
bopType Eq = (TInteger, TInteger, TBool)
bopType Less = (TInteger, TInteger, TBool)
infer :: Ctx -> Arith -> Either TypeError Type
infer ctx (Lit _) = Right TInteger
infer ctx BTrue = Right TBool
infer ctx BFalse = Right TBool
infer ctx (Bin op e1 e2) = do
let (t1,t2, tOut) = bopType op
check ctx e1 t1
check ctx e2 t2
return tOut
infer ctx (Var v) = case M.lookup v ctx of
Just x -> Right x
Nothing -> Left $ UndefinedVar v
infer ctx e@(If cond eThen eElse) = do
check ctx cond TBool
t1 <- infer ctx eThen
t2 <- infer ctx eElse
if t1 /= t2 then Left $ IfBranchesMismatch e t1 t2
else Right t1
infer ctx (Let name val expr) = do
t <- infer ctx val
infer (M.insert name t ctx) expr
check :: Ctx -> Arith -> Type -> Either TypeError ()
check ctx e t = do
t1 <- infer ctx e
if t == t1 then return ()
else Left $ TypeMismatch e t t1
inferArith :: Arith -> Either TypeError Type
inferArith = infer M.empty
interpArith :: Env -> Arith -> Either InterpError Integer
interpArith _ (Lit i) = Right i
interpArith _ BTrue = Right 1
interpArith _ BFalse = Right 0
interpArith env (Bin Plus e1 e2) = (+) <$> interpArith env e1 <*> interpArith env e2
interpArith env (Bin Minus e1 e2) = (-) <$> interpArith env e1 <*> interpArith env e2
interpArith env (Bin Times e1 e2) = (*) <$> interpArith env e1 <*> interpArith env e2
interpArith env (Bin Div e1 e2) =
(interpArith env e2 >>= div') <*> interpArith env e1
where
div' 0 = Left DivisonByZero
div' x = Right (\y -> x `div` y)
interpArith env (Bin Less e1 e2) = less <$> interpArith env e1 <*> interpArith env e2
where less x y = if x < y then 1 else 0
interpArith env (Bin Eq e1 e2) = eq <$> interpArith env e1 <*> interpArith env e2
where eq x y = if x == y then 1 else 0
interpArith env (Var v) = case M.lookup v env of
Just x -> Right x
Nothing -> error "Bug: undefined var not caught by type check"
interpArith env (Let name val expr) =
interpArith env val >>= (\x -> interpArith (M.insert name x env) expr)
interpArith env (If cond eTrue eFalse) = do
cond' <- interpArith env cond
if cond' == 1 then interpArith env eTrue
else interpArith env eFalse
lexer :: TokenParser u
lexer = makeTokenParser $ emptyDef
{ reservedNames = ["let", "in", "True", "False", "if", "then", "else"] }
-- tell the lexer that "let" and "in" are reserved keywords
-- which may not be used as variable names
parens :: Parser a -> Parser a
parens = getParens lexer
reservedOp :: String -> Parser ()
reservedOp = getReservedOp lexer
reserved :: String -> Parser ()
reserved = getReserved lexer
integer :: Parser Integer
integer = getInteger lexer
whiteSpace :: Parser ()
whiteSpace = getWhiteSpace lexer
identifier :: Parser String
identifier = getIdentifier lexer
parseVar :: Parser FullArith
parseVar = FVar <$> identifier
parseArithAtom :: Parser FullArith
parseArithAtom =
(FLit <$> integer) <|>
parens parseArith <|>
parseLet <|>
parseVar <|>
parseIf <|>
(FTrue <$ reserved "True") <|>
(FFalse <$ reserved "False")
parseLet :: Parser FullArith
parseLet =
FLet <$ reserved "let"
<*> identifier
<* reserved "="
<*> parseArith
<* reserved "in"
<*> parseArith
parseIf :: Parser FullArith
parseIf =
FIf <$ reserved "if"
<*> parseArith
<* reserved "then"
<*> parseArith
<* reserved "else"
<*> parseArith
parseArith :: Parser FullArith
parseArith = buildExpressionParser table parseArithAtom
where
table = [ [ Infix (FBin (ArOp Times) <$ reservedOp "*") AssocLeft
, Infix (FBin (ArOp Div) <$ reservedOp "/") AssocLeft
]
, [ Infix (FBin (ArOp Plus) <$ reservedOp "+") AssocLeft
, Infix (FBin (ArOp Minus) <$ reservedOp "-") AssocLeft
]
, [ Prefix (FUn Not <$ reservedOp "!")
]
, [ Infix (FBin (ArOp Less) <$ reservedOp "<") AssocNone
, Infix (FBin (ArOp Eq) <$ reservedOp "==") AssocNone
, Infix (FBin Gt <$ reservedOp ">") AssocNone
, Infix (FBin Le <$ reservedOp "<=") AssocNone
, Infix (FBin Ge <$ reservedOp ">=") AssocNone
, Infix (FBin Ne <$ reservedOp "!=") AssocNone
]
, [ Infix (FBin And <$ reservedOp "&&") AssocRight
]
, [ Infix (FBin Or <$ reservedOp "||") AssocRight
]
]
desugar :: FullArith -> Arith
desugar (FLit i) = Lit i
desugar FFalse = BFalse
desugar FTrue = BTrue
desugar (FVar v) = Var v
desugar (FIf c e1 e2) = If (desugar c) (desugar e1) (desugar e2)
desugar (FLet n v e) = Let n (desugar v) (desugar e)
desugar (FBin (ArOp op) e1 e2) = Bin op (desugar e1) (desugar e2)
desugar (FUn Not e) = If (desugar e) BFalse BTrue
desugar (FBin Ne e1 e2) = desugar (FUn Not (FBin (ArOp Eq) e1 e2))
desugar (FBin Le e1 e2) = desugar (FUn Not (FBin (ArOp Less) e2 e1))
desugar (FBin Gt e1 e2) = desugar (FBin (ArOp Less) e2 e1)
desugar (FBin Ge e1 e2) = desugar (FUn Not (FBin (ArOp Less) e1 e2))
desugar (FBin And e1 e2) = desugar (FIf e1 e2 FFalse)
desugar (FBin Or e1 e2) = desugar (FIf e1 FTrue e2)
arith :: Parser Arith
arith = whiteSpace *> (desugar <$> parseArith) <* eof
showAsType :: Type -> Integer -> String
showAsType TBool 0 = "False"
showAsType TBool 1 = "True"
showAsType _ x = show x
eval :: String -> IO ()
eval s = case parse arith s of
Left err -> print err
Right e -> case inferArith e of
Left err -> putStrLn (showTypeError err)
Right t -> case interpArith M.empty e of
Left err -> putStrLn (showInterpError err)
Right val -> putStrLn $ showAsType t val