1 {-# LANGUAGE FlexibleContexts #-}
2 {-# LANGUAGE FlexibleInstances #-}
4 {-# LANGUAGE MultiParamTypeClasses #-}
5 {-# LANGUAGE OverloadedStrings #-}
6 {-# LANGUAGE Rank2Types #-}
7 {-# LANGUAGE ScopedTypeVariables #-}
8 {-# LANGUAGE TypeFamilies #-}
9 {-# LANGUAGE UndecidableInstances #-}
10 -- | Abstract Syntax Tree.
14 -- import Test.Tasty.HUnit
16 import qualified Data.List as List
17 import Data.Proxy (Proxy(..))
18 import Data.Text (Text)
19 import qualified Data.Text as Text
21 import Language.Symantic.Type
22 import Language.Symantic.Expr as Expr
25 tests = testGroup "AST" $
33 -- | Custom 'Show' instance a little bit more readable
34 -- than the automatically derived one.
35 instance Show AST where
36 showsPrec p ast@(AST f args) =
37 let n = Text.unpack f in
39 AST _ [] -> showString n
41 showParen (p >= prec_arrow) $
42 showString ("("++n++") ") .
43 showsPrec prec_arrow a
45 showParen (p >= prec_arrow) $
46 showsPrec prec_arrow a .
47 showString (" "++n++" ") .
48 showsPrec prec_arrow b
52 showString (List.intercalate ", " $ show <$> args) .
56 -- ** Parsing utilities
58 :: forall ty ast ex hs ret.
59 ( ty ~ Type_Root_of_Expr ex
60 , Error_Expr_Lift (Error_Expr (Error_of_Type ast ty) ty ast)
61 (Error_of_Expr ast (Root_of_Expr ex))
63 -> Expr_From ast ex hs ret
64 -> Expr_From ast ex hs ret
65 from_ast0 asts k' ex ast ctx k =
68 _ -> Left $ error_expr ex $
69 Error_Expr_Wrong_number_of_arguments ast 0
72 :: forall ty ast ex hs ret.
73 ( ty ~ Type_Root_of_Expr ex
74 , Error_Expr_Lift (Error_Expr (Error_of_Type ast ty) ty ast)
75 (Error_of_Expr ast (Root_of_Expr ex))
76 ) => [ast] -> (ast -> Expr_From ast ex hs ret)
77 -> Expr_From ast ex hs ret
78 from_ast1 asts k' ex ast ctx k =
80 [ast_0] -> k' ast_0 ex ast ctx k
81 _ -> Left $ error_expr ex $
82 Error_Expr_Wrong_number_of_arguments ast 1
85 :: forall ty ast ex hs ret.
86 ( ty ~ Type_Root_of_Expr ex
87 , Error_Expr_Lift (Error_Expr (Error_of_Type ast ty) ty ast)
88 (Error_of_Expr ast (Root_of_Expr ex))
89 ) => [ast] -> (ast -> ast -> Expr_From ast ex hs ret)
90 -> Expr_From ast ex hs ret
91 from_ast2 asts k' ex ast ctx k =
93 [ast_0, ast_1] -> k' ast_0 ast_1 ex ast ctx k
94 _ -> Left $ error_expr ex $
95 Error_Expr_Wrong_number_of_arguments ast 2
98 :: forall ty ast ex hs ret.
99 ( ty ~ Type_Root_of_Expr ex
100 , Error_Expr_Lift (Error_Expr (Error_of_Type ast ty) ty ast)
101 (Error_of_Expr ast (Root_of_Expr ex))
102 ) => [ast] -> (ast -> ast -> ast -> Expr_From ast ex hs ret)
103 -> Expr_From ast ex hs ret
104 from_ast3 asts k' ex ast ctx k =
106 [ast_0, ast_1, ast_2] -> k' ast_0 ast_1 ast_2 ex ast ctx k
107 _ -> Left $ error_expr ex $
108 Error_Expr_Wrong_number_of_arguments ast 3
111 :: forall root ty lit ex ast hs ret.
112 ( ty ~ Type_Root_of_Expr ex
113 , root ~ Root_of_Expr ex
116 , Error_Expr_Lift (Error_Expr (Error_of_Type ast ty) ty ast)
117 (Error_of_Expr ast root)
118 ) => (forall repr. Sym_of_Expr ex repr => lit -> repr lit)
120 -> Expr_From ast ex hs ret
121 lit_from_AST op ty_lit asts ex ast ctx k =
123 [AST lit []] -> lit_from op ty_lit lit ex ast ctx k
124 _ -> Left $ error_expr ex $
125 Error_Expr_Wrong_number_of_arguments ast 1
128 :: forall root ty lit ex ast hs ret.
129 ( ty ~ Type_Root_of_Expr ex
130 , root ~ Root_of_Expr ex
132 , Eq_Type (Type_Root_of_Expr root)
134 , Error_Expr_Lift (Error_Expr (Error_of_Type ast ty) ty ast)
135 (Error_of_Expr ast root)
136 , Root_of_Expr root ~ root
137 ) => (forall repr. Sym_of_Expr ex repr => repr lit -> repr lit)
139 -> Expr_From ast ex hs ret
140 op1_from_AST op ty_lit asts ex ast ctx k =
142 [ast_x] -> op1_from op ty_lit ast_x ex ast ctx k
143 _ -> Left $ error_expr ex $
144 Error_Expr_Wrong_number_of_arguments ast 1
147 :: forall root ty lit ex ast hs ret.
148 ( ty ~ Type_Root_of_Expr ex
149 , root ~ Root_of_Expr ex
151 , Eq_Type (Type_Root_of_Expr root)
153 , Error_Expr_Lift (Error_Expr (Error_of_Type ast ty) ty ast)
154 (Error_of_Expr ast root)
155 , Root_of_Expr root ~ root
156 ) => (forall repr. Sym_of_Expr ex repr => repr lit -> repr lit -> repr lit)
158 -> Expr_From ast ex hs ret
159 op2_from_AST op ty_lit asts ex ast ctx k =
161 [ast_x, ast_y] -> op2_from op ty_lit ast_x ast_y ex ast ctx k
162 _ -> Left $ error_expr ex $
163 Error_Expr_Wrong_number_of_arguments ast 2
165 instance -- Type_from AST Type_Var
166 ( Error_Type_Lift (Error_Type AST) (Error_of_Type AST root)
167 , Implicit_HBool (Is_Last_Type (Type_Var root) root)
168 ) => Type_from AST (Type_Var root) where
169 type_from ty ast _k =
170 Left $ error_type_unsupported ty ast
171 -- NOTE: no support so far.
172 instance -- Type_from AST Type_Unit
173 ( Type_Root_Lift Type_Unit root
174 , Error_Type_Lift (Error_Type AST) (Error_of_Type AST root)
175 , Implicit_HBool (Is_Last_Type (Type_Unit root) root)
176 ) => Type_from AST (Type_Unit root) where
182 _ -> Left $ error_type_lift $
183 Error_Type_Wrong_number_of_arguments ast 0
184 _ -> Left $ error_type_unsupported ty ast
185 instance -- Type_from AST Type_Bool
186 ( Type_Root_Lift Type_Bool root
187 , Error_Type_Lift (Error_Type AST) (Error_of_Type AST root)
188 , Implicit_HBool (Is_Last_Type (Type_Bool root) root)
189 ) => Type_from AST (Type_Bool root) where
195 _ -> Left $ error_type_lift $
196 Error_Type_Wrong_number_of_arguments ast 0
197 _ -> Left $ error_type_unsupported ty ast
198 instance -- Type_from AST Type_Int
199 ( Type_Root_Lift Type_Int root
200 , Error_Type_Lift (Error_Type AST) (Error_of_Type AST root)
201 , Implicit_HBool (Is_Last_Type (Type_Int root) root)
202 ) => Type_from AST (Type_Int root) where
208 _ -> Left $ error_type_lift $
209 Error_Type_Wrong_number_of_arguments ast 0
210 _ -> Left $ error_type_unsupported ty ast
211 instance -- Type_from AST Type_Fun
214 , Type_Root_Lift (Type_Fun lam) root
215 , Error_Type_Lift (Error_Type AST) (Error_of_Type AST root)
216 , Error_Type_Unlift (Error_Type AST) (Error_of_Type AST root)
217 , Root_of_Type root ~ root
218 , Implicit_HBool (Is_Last_Type (Type_Fun lam root) root)
219 ) => Type_from AST (Type_Fun lam root) where
224 [ast_arg, ast_res] -> type_fun_from ty ast_arg ast_res k
225 _ -> Left $ error_type_lift $
226 Error_Type_Wrong_number_of_arguments ast 2
227 _ -> Left $ error_type_unsupported ty ast
228 instance -- Type_from AST Type_Maybe
231 , Type_Root_Lift Type_Maybe root
232 , Error_Type_Lift (Error_Type AST) (Error_of_Type AST root)
233 , Error_Type_Unlift (Error_Type AST) (Error_of_Type AST root)
234 , Root_of_Type root ~ root
235 , Implicit_HBool (Is_Last_Type (Type_Maybe root) root)
236 ) => Type_from AST (Type_Maybe root) where
242 type_from (Proxy::Proxy root) ast_a $ \ty_a ->
244 _ -> Left $ error_type_lift $
245 Error_Type_Wrong_number_of_arguments ast 1
246 _ -> Left $ error_type_unsupported ty ast
247 instance -- Type_from AST Type_List
250 , Type_Root_Lift Type_List root
251 , Error_Type_Lift (Error_Type AST) (Error_of_Type AST root)
252 , Error_Type_Unlift (Error_Type AST) (Error_of_Type AST root)
253 , Root_of_Type root ~ root
254 , Implicit_HBool (Is_Last_Type (Type_List root) root)
255 ) => Type_from AST (Type_List root) where
261 type_from (Proxy::Proxy root) ast_a $ \ty_a ->
263 _ -> Left $ error_type_lift $
264 Error_Type_Wrong_number_of_arguments ast 1
265 _ -> Left $ error_type_unsupported ty ast
266 instance -- Expr_from AST Expr_Bool
267 ( Type_from AST (Type_Root_of_Expr root)
269 , Type_Root_Lift Type_Bool (Type_Root_of_Expr root)
270 , Error_Expr_Lift (Error_Expr_of_Root AST root) (Error_of_Expr AST root)
271 , Type_Unlift Type_Bool (Type_of_Expr root)
272 , Root_of_Expr root ~ root
273 , Implicit_HBool (Is_Last_Expr (Expr_Bool root) root)
274 ) => Expr_from AST (Expr_Bool root) where
277 AST "bool" asts -> lit_from_AST bool type_bool asts ex ast
278 AST "not" asts -> op1_from_AST Expr.not type_bool asts ex ast
279 AST "&&" asts -> op2_from_AST (Expr.&&) type_bool asts ex ast
280 AST "||" asts -> op2_from_AST (Expr.||) type_bool asts ex ast
281 AST "xor" asts -> op2_from_AST Expr.xor type_bool asts ex ast
282 _ -> \_ctx _k -> Left $ error_expr_unsupported ex ast
283 instance -- Expr_from AST Expr_If
284 ( Type_from AST (Type_Root_of_Expr root)
286 , Type_Root_Lift Type_Bool (Type_Root_of_Expr root)
287 , Error_Expr_Lift (Error_Expr_of_Root AST root) (Error_of_Expr AST root)
288 , Root_of_Expr root ~ root
289 , Implicit_HBool (Is_Last_Expr (Expr_If root) root)
290 ) => Expr_from AST (Expr_If root) where
291 expr_from ex ast ctx k =
293 AST "if" asts -> from_ast3 asts if_from ex ast ctx k
294 _ -> Left $ error_expr_unsupported ex ast
295 instance -- Expr_from AST Expr_When
296 ( Type_from AST (Type_Root_of_Expr root)
298 , Type_Root_Lift Type_Bool (Type_Root_of_Expr root)
299 , Type_Root_Lift Type_Unit (Type_Root_of_Expr root)
300 , Error_Expr_Lift (Error_Expr_of_Root AST root) (Error_of_Expr AST root)
301 , Root_of_Expr root ~ root
302 , Implicit_HBool (Is_Last_Expr (Expr_When root) root)
303 ) => Expr_from AST (Expr_When root) where
304 expr_from ex ast ctx k =
306 AST "when" asts -> from_ast2 asts when_from ex ast ctx k
307 _ -> Left $ error_expr_unsupported ex ast
308 instance -- Expr_from AST Expr_Int
309 ( Type_from AST (Type_Root_of_Expr root)
311 , Type_Root_Lift Type_Int (Type_Root_of_Expr root)
312 , Error_Expr_Lift (Error_Expr_of_Root AST root) (Error_of_Expr AST root)
313 , Type_Unlift Type_Int (Type_of_Expr root)
314 , Root_of_Expr root ~ root
315 , Implicit_HBool (Is_Last_Expr (Expr_Int root) root)
316 ) => Expr_from AST (Expr_Int root) where
319 AST "int" asts -> lit_from_AST int type_int asts ex ast
320 AST "abs" asts -> op1_from_AST Expr.abs type_int asts ex ast
321 AST "negate" asts -> op1_from_AST Expr.negate type_int asts ex ast
322 AST "+" asts -> op2_from_AST (Expr.+) type_int asts ex ast
323 AST "-" asts -> op2_from_AST (Expr.-) type_int asts ex ast
324 AST "*" asts -> op2_from_AST (Expr.*) type_int asts ex ast
325 AST "mod" asts -> op2_from_AST Expr.mod type_int asts ex ast
326 _ -> \_ctx _k -> Left $ error_expr_unsupported ex ast
327 instance -- Expr_from AST Expr_Lambda
328 ( Type_from AST (Type_Root_of_Expr root)
330 , Type_Root_Lift (Type_Fun lam) (Type_Root_of_Expr root)
331 , Error_Expr_Lift (Error_Expr_Lambda AST) (Error_of_Expr AST root)
332 , Error_Expr_Lift (Error_Expr_of_Root AST root) (Error_of_Expr AST root)
333 , Type_Unlift (Type_Fun lam) (Type_of_Expr root)
334 , Root_of_Expr root ~ root
335 , Implicit_HBool (Is_Last_Expr (Expr_Lambda lam root) root)
336 ) => Expr_from AST (Expr_Lambda lam root) where
337 expr_from ex ast ctx k =
341 [AST name []] -> var_from name ex ast ctx k
342 _ -> Left $ error_expr ex $
343 Error_Expr_Wrong_number_of_arguments ast 1
344 AST "app" asts -> from_ast2 asts app_from ex ast ctx k
345 AST "inline" asts -> go_lam asts inline
346 AST "val" asts -> go_lam asts val
347 AST "lazy" asts -> go_lam asts lazy
348 AST "let_inline" asts -> go_let asts let_inline
349 AST "let_val" asts -> go_let asts let_val
350 AST "let_lazy" asts -> go_let asts let_lazy
351 _ -> Left $ error_expr_unsupported ex ast
354 (lam::forall repr arg res. Sym_Lambda lam repr
355 => (repr arg -> repr res) -> repr (Lambda lam arg res)) =
357 [AST name [], ast_ty_arg, ast_body] ->
358 lam_from lam name ast_ty_arg ast_body ex ast ctx k
359 _ -> Left $ error_expr ex $
360 Error_Expr_Wrong_number_of_arguments ast 3
362 (let_::forall repr var res. Sym_Lambda lam repr
363 => repr var -> (repr var -> repr res) -> repr res) =
365 [AST name [], ast_var, ast_body] ->
366 let_from let_ name ast_var ast_body ex ast ctx k
367 _ -> Left $ error_expr ex $
368 Error_Expr_Wrong_number_of_arguments ast 3
369 instance -- Expr_from AST Expr_Maybe
370 ( Type_from AST (Type_Root_of_Expr root)
372 , Type_Lift (Type_Fun lam) (Type_of_Expr root)
373 , Type_Unlift (Type_Fun lam) (Type_of_Expr root)
374 , Type_Lift Type_Maybe (Type_of_Expr root)
375 , Type_Unlift Type_Maybe (Type_of_Expr root)
376 , Error_Expr_Lift (Error_Expr_of_Root AST root) (Error_of_Expr AST root)
377 , Root_of_Expr root ~ root
378 , Implicit_HBool (Is_Last_Expr (Expr_Maybe lam root) root)
379 ) => Expr_from AST (Expr_Maybe lam root) where
380 expr_from ex ast ctx k =
382 AST "maybe" asts -> from_ast3 asts maybe_from ex ast ctx k
383 AST "nothing" asts -> from_ast1 asts nothing_from ex ast ctx k
384 AST "just" asts -> from_ast1 asts just_from ex ast ctx k
385 _ -> Left $ error_expr_unsupported ex ast
386 instance -- Expr_from AST Expr_Eq
387 ( Type_from AST (Type_Root_of_Expr root)
388 , Type_Lift Type_Bool (Type_of_Expr root)
389 , Constraint_Type Eq (Type_Root_of_Expr root)
391 , Error_Expr_Lift (Error_Expr_of_Root AST root) (Error_of_Expr AST root)
392 , Root_of_Expr root ~ root
393 , Implicit_HBool (Is_Last_Expr (Expr_Eq root) root)
394 ) => Expr_from AST (Expr_Eq root) where
395 expr_from ex ast ctx k =
397 AST "==" asts -> from_ast2 asts eq_from ex ast ctx k
398 _ -> Left $ error_expr_unsupported ex ast
399 instance -- Expr_from AST Expr_Ord
400 ( Type_from AST (Type_Root_of_Expr root)
401 , Type_Lift Type_Ordering (Type_of_Expr root)
402 , Constraint_Type Ord (Type_Root_of_Expr root)
404 , Error_Expr_Lift (Error_Expr_of_Root AST root) (Error_of_Expr AST root)
405 , Root_of_Expr root ~ root
406 , Implicit_HBool (Is_Last_Expr (Expr_Ord root) root)
407 ) => Expr_from AST (Expr_Ord root) where
408 expr_from ex ast ctx k =
410 AST "compare" asts -> from_ast2 asts compare_from ex ast ctx k
411 _ -> Left $ error_expr_unsupported ex ast
412 instance -- Expr_from AST Expr_List
413 ( Type_from AST (Type_Root_of_Expr root)
415 , Type_Lift (Type_Fun lam) (Type_of_Expr root)
416 , Type_Unlift (Type_Fun lam) (Type_of_Expr root)
417 , Type_Lift Type_List (Type_of_Expr root)
418 , Type_Unlift Type_List (Type_of_Expr root)
419 , Type_Lift Type_Bool (Type_of_Expr root)
420 , Error_Expr_Lift (Error_Expr_of_Root AST root) (Error_of_Expr AST root)
421 , Root_of_Expr root ~ root
422 , Implicit_HBool (Is_Last_Expr (Expr_List lam root) root)
423 ) => Expr_from AST (Expr_List lam root) where
424 expr_from ex ast ctx k =
426 AST "[]" asts -> from_ast1 asts list_empty_from ex ast ctx k
427 AST ":" asts -> from_ast2 asts list_cons_from ex ast ctx k
428 AST "list_filter" asts -> from_ast2 asts list_filter_from ex ast ctx k
431 ast_ty_a:asts' -> list_from ast_ty_a asts' ex ast ctx k
432 _ -> Left $ error_expr ex $
433 Error_Expr_Wrong_number_of_arguments ast 1
434 _ -> Left $ error_expr_unsupported ex ast
435 instance -- Expr_from AST Expr_Map
436 ( Type_from AST (Type_Root_of_Expr root)
438 , Type_Lift (Type_Fun lam) (Type_of_Expr root)
439 , Type_Unlift (Type_Fun lam) (Type_of_Expr root)
440 , Type_Lift Type_Map (Type_of_Expr root)
441 , Type_Unlift Type_Map (Type_of_Expr root)
442 , Type_Lift Type_List (Type_of_Expr root)
443 , Type_Unlift Type_List (Type_of_Expr root)
444 , Type_Lift Type_Tuple2 (Type_of_Expr root)
445 , Type_Unlift Type_Tuple2 (Type_of_Expr root)
446 , Constraint_Type Ord (Type_Root_of_Expr root)
447 , Error_Expr_Lift (Error_Expr_of_Root AST root) (Error_of_Expr AST root)
448 , Root_of_Expr root ~ root
449 , Implicit_HBool (Is_Last_Expr (Expr_Map lam root) root)
450 ) => Expr_from AST (Expr_Map lam root) where
451 expr_from ex ast ctx k =
453 AST "map_from_list" asts -> from_ast1 asts map_from_list_from ex ast ctx k
454 AST "map_map" asts -> from_ast2 asts map_map_from ex ast ctx k
455 _ -> Left $ error_expr_unsupported ex ast
456 instance -- Expr_from AST Expr_Functor
457 ( Type_from AST (Type_Root_of_Expr root)
459 , Type_Lift (Type_Fun lam) (Type_of_Expr root)
460 , Type_Unlift (Type_Fun lam) (Type_of_Expr root)
461 , Type_Unlift1 (Type_of_Expr root)
462 , Error_Expr_Lift (Error_Expr_of_Root AST root) (Error_of_Expr AST root)
463 , Constraint1_Type Functor_with_Lambda (Type_Root_of_Expr root)
464 , Root_of_Expr root ~ root
465 , Implicit_HBool (Is_Last_Expr (Expr_Functor lam root) root)
466 ) => Expr_from AST (Expr_Functor lam root) where
467 expr_from ex ast ctx k =
469 AST "fmap" asts -> from_ast2 asts fmap_from ex ast ctx k
470 _ -> Left $ error_expr_unsupported ex ast