]> Git — Sourcephile - haskell/symantic.git/blob - Language/Symantic/AST/Test.hs
init
[haskell/symantic.git] / Language / Symantic / AST / Test.hs
1 {-# LANGUAGE FlexibleContexts #-}
2 {-# LANGUAGE FlexibleInstances #-}
3 {-# LANGUAGE GADTs #-}
4 {-# LANGUAGE MultiParamTypeClasses #-}
5 {-# LANGUAGE OverloadedStrings #-}
6 {-# LANGUAGE Rank2Types #-}
7 {-# LANGUAGE ScopedTypeVariables #-}
8 {-# LANGUAGE TypeFamilies #-}
9 {-# LANGUAGE UndecidableInstances #-}
10 -- | Abstract Syntax Tree.
11 module AST.Test where
12
13 import Test.Tasty
14 -- import Test.Tasty.HUnit
15
16 import qualified Data.List as List
17 import Data.Proxy (Proxy(..))
18 import Data.Text (Text)
19 import qualified Data.Text as Text
20
21 import Language.Symantic.Type
22 import Language.Symantic.Expr as Expr
23
24 tests :: TestTree
25 tests = testGroup "AST" $
26 [
27 ]
28
29 -- * Type 'AST'
30 data AST
31 = AST Text [AST]
32 deriving (Eq)
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
38 case ast of
39 AST _ [] -> showString n
40 AST "->" [a] ->
41 showParen (p >= prec_arrow) $
42 showString ("("++n++") ") .
43 showsPrec prec_arrow a
44 AST "->" [a, b] ->
45 showParen (p >= prec_arrow) $
46 showsPrec prec_arrow a .
47 showString (" "++n++" ") .
48 showsPrec prec_arrow b
49 _ ->
50 showString n .
51 showString "(" .
52 showString (List.intercalate ", " $ show <$> args) .
53 showString ")"
54 where prec_arrow = 1
55
56 -- ** Parsing utilities
57 from_ast0
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))
62 ) => [ast]
63 -> Expr_From ast ex hs ret
64 -> Expr_From ast ex hs ret
65 from_ast0 asts k' ex ast ctx k =
66 case asts of
67 [] -> k' ex ast ctx k
68 _ -> Left $ error_expr ex $
69 Error_Expr_Wrong_number_of_arguments ast 0
70
71 from_ast1
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 =
79 case asts of
80 [ast_0] -> k' ast_0 ex ast ctx k
81 _ -> Left $ error_expr ex $
82 Error_Expr_Wrong_number_of_arguments ast 1
83
84 from_ast2
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 =
92 case asts of
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
96
97 from_ast3
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 =
105 case asts of
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
109
110 lit_from_AST
111 :: forall root ty lit ex ast hs ret.
112 ( ty ~ Type_Root_of_Expr ex
113 , root ~ Root_of_Expr ex
114 , ast ~ AST
115 , Read lit
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)
119 -> ty lit -> [ast]
120 -> Expr_From ast ex hs ret
121 lit_from_AST op ty_lit asts ex ast ctx k =
122 case asts of
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
126
127 op1_from_AST
128 :: forall root ty lit ex ast hs ret.
129 ( ty ~ Type_Root_of_Expr ex
130 , root ~ Root_of_Expr ex
131 , ast ~ AST
132 , Type_Eq (Type_Root_of_Expr root)
133 , Expr_from ast 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)
138 -> ty lit -> [ast]
139 -> Expr_From ast ex hs ret
140 op1_from_AST op ty_lit asts ex ast ctx k =
141 case asts of
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
145
146 op2_from_AST
147 :: forall root ty lit ex ast hs ret.
148 ( ty ~ Type_Root_of_Expr ex
149 , root ~ Root_of_Expr ex
150 , ast ~ AST
151 , Type_Eq (Type_Root_of_Expr root)
152 , Expr_from ast 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)
157 -> ty lit -> [ast]
158 -> Expr_From ast ex hs ret
159 op2_from_AST op ty_lit asts ex ast ctx k =
160 case asts of
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
164
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
177 type_from ty ast k =
178 case ast of
179 AST "()" asts ->
180 case asts of
181 [] -> k type_unit
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
190 type_from ty ast k =
191 case ast of
192 AST "Bool" asts ->
193 case asts of
194 [] -> k type_bool
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
203 type_from ty ast k =
204 case ast of
205 AST "Int" asts ->
206 case asts of
207 [] -> k type_int
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
212 ( Type_Eq root
213 , Type_from AST root
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
220 type_from ty ast k =
221 case ast of
222 AST "->" asts ->
223 case asts of
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
229 ( Type_Eq root
230 , Type_from AST root
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
237 type_from ty ast k =
238 case ast of
239 AST "Maybe" asts ->
240 case asts of
241 [ast_a] ->
242 type_from (Proxy::Proxy root) ast_a $ \(ty_a::root h_a) ->
243 k (type_root_lift $ Type_Maybe ty_a
244 :: root (Maybe h_a))
245 _ -> Left $ error_type_lift $
246 Error_Type_Wrong_number_of_arguments ast 1
247 _ -> Left $ error_type_unsupported ty ast
248 instance -- Expr_from AST Expr_Bool
249 ( Type_from AST (Type_Root_of_Expr root)
250 , Expr_from AST root
251 , Type_Root_Lift Type_Bool (Type_Root_of_Expr root)
252 , Error_Expr_Lift (Error_Expr_of_Root AST root) (Error_of_Expr AST root)
253 , Type_Unlift Type_Bool (Type_of_Expr root)
254 , Root_of_Expr root ~ root
255 , Implicit_HBool (Is_Last_Expr (Expr_Bool root) root)
256 ) => Expr_from AST (Expr_Bool root) where
257 expr_from ex ast =
258 case ast of
259 AST "bool" asts -> lit_from_AST bool type_bool asts ex ast
260 AST "not" asts -> op1_from_AST Expr.not type_bool asts ex ast
261 AST "&&" asts -> op2_from_AST (Expr.&&) type_bool asts ex ast
262 AST "||" asts -> op2_from_AST (Expr.||) type_bool asts ex ast
263 AST "xor" asts -> op2_from_AST Expr.xor type_bool asts ex ast
264 _ -> \_ctx _k -> Left $ error_expr_unsupported ex ast
265 instance -- Expr_from AST Expr_If
266 ( Type_from AST (Type_Root_of_Expr root)
267 , Expr_from AST root
268 , Type_Root_Lift Type_Bool (Type_Root_of_Expr root)
269 , Error_Expr_Lift (Error_Expr_of_Root AST root) (Error_of_Expr AST root)
270 , Root_of_Expr root ~ root
271 , Implicit_HBool (Is_Last_Expr (Expr_If root) root)
272 ) => Expr_from AST (Expr_If root) where
273 expr_from ex ast ctx k =
274 case ast of
275 AST "if" asts -> from_ast3 asts if_from ex ast ctx k
276 _ -> Left $ error_expr_unsupported ex ast
277 instance -- Expr_from AST Expr_When
278 ( Type_from AST (Type_Root_of_Expr root)
279 , Expr_from AST root
280 , Type_Root_Lift Type_Bool (Type_Root_of_Expr root)
281 , Type_Root_Lift Type_Unit (Type_Root_of_Expr root)
282 , Error_Expr_Lift (Error_Expr_of_Root AST root) (Error_of_Expr AST root)
283 , Root_of_Expr root ~ root
284 , Implicit_HBool (Is_Last_Expr (Expr_When root) root)
285 ) => Expr_from AST (Expr_When root) where
286 expr_from ex ast ctx k =
287 case ast of
288 AST "when" asts -> from_ast2 asts when_from ex ast ctx k
289 _ -> Left $ error_expr_unsupported ex ast
290 instance -- Expr_from AST Expr_Int
291 ( Type_from AST (Type_Root_of_Expr root)
292 , Expr_from AST root
293 , Type_Root_Lift Type_Int (Type_Root_of_Expr root)
294 , Error_Expr_Lift (Error_Expr_of_Root AST root) (Error_of_Expr AST root)
295 , Type_Unlift Type_Int (Type_of_Expr root)
296 , Root_of_Expr root ~ root
297 , Implicit_HBool (Is_Last_Expr (Expr_Int root) root)
298 ) => Expr_from AST (Expr_Int root) where
299 expr_from ex ast =
300 case ast of
301 AST "int" asts -> lit_from_AST int type_int asts ex ast
302 AST "abs" asts -> op1_from_AST Expr.abs type_int asts ex ast
303 AST "negate" asts -> op1_from_AST Expr.negate type_int asts ex ast
304 AST "+" asts -> op2_from_AST (Expr.+) type_int asts ex ast
305 AST "-" asts -> op2_from_AST (Expr.-) type_int asts ex ast
306 AST "*" asts -> op2_from_AST (Expr.*) type_int asts ex ast
307 AST "mod" asts -> op2_from_AST Expr.mod type_int asts ex ast
308 _ -> \_ctx _k -> Left $ error_expr_unsupported ex ast
309 instance -- Expr_from AST Expr_Lambda
310 ( Type_from AST (Type_Root_of_Expr root)
311 , Expr_from AST root
312 , Type_Root_Lift (Type_Fun lam) (Type_Root_of_Expr root)
313 , Error_Expr_Lift (Error_Expr_Lambda AST) (Error_of_Expr AST root)
314 , Error_Expr_Lift (Error_Expr_of_Root AST root) (Error_of_Expr AST root)
315 , Type_Unlift (Type_Fun lam) (Type_of_Expr root)
316 , Root_of_Expr root ~ root
317 , Implicit_HBool (Is_Last_Expr (Expr_Lambda lam root) root)
318 ) => Expr_from AST (Expr_Lambda lam root) where
319 expr_from ex ast ctx k =
320 case ast of
321 AST "var" asts ->
322 case asts of
323 [AST name []] -> var_from name ex ast ctx k
324 _ -> Left $ error_expr ex $
325 Error_Expr_Wrong_number_of_arguments ast 1
326 AST "app" asts -> from_ast2 asts app_from ex ast ctx k
327 AST "inline" asts -> go_lam asts inline
328 AST "val" asts -> go_lam asts val
329 AST "lazy" asts -> go_lam asts lazy
330 AST "let_inline" asts -> go_let asts let_inline
331 AST "let_val" asts -> go_let asts let_val
332 AST "let_lazy" asts -> go_let asts let_lazy
333 _ -> Left $ error_expr_unsupported ex ast
334 where
335 go_lam asts
336 (lam::forall repr arg res. Sym_Lambda lam repr
337 => (repr arg -> repr res) -> repr (Lambda lam arg res)) =
338 case asts of
339 [AST name [], ast_ty_arg, ast_body] ->
340 lam_from lam name ast_ty_arg ast_body ex ast ctx k
341 _ -> Left $ error_expr ex $
342 Error_Expr_Wrong_number_of_arguments ast 3
343 go_let asts
344 (let_::forall repr var res. Sym_Lambda lam repr
345 => repr var -> (repr var -> repr res) -> repr res) =
346 case asts of
347 [AST name [], ast_var, ast_body] ->
348 let_from let_ name ast_var ast_body ex ast ctx k
349 _ -> Left $ error_expr ex $
350 Error_Expr_Wrong_number_of_arguments ast 3
351 instance -- Expr_from AST Expr_Maybe
352 ( Type_from AST (Type_Root_of_Expr root)
353 , Expr_from AST root
354 , Type_Lift (Type_Fun lam) (Type_of_Expr root)
355 , Type_Unlift (Type_Fun lam) (Type_of_Expr root)
356 , Type_Lift Type_Maybe (Type_of_Expr root)
357 , Type_Unlift Type_Maybe (Type_of_Expr root)
358 , Error_Expr_Lift (Error_Expr_of_Root AST root) (Error_of_Expr AST root)
359 , Root_of_Expr root ~ root
360 , Implicit_HBool (Is_Last_Expr (Expr_Maybe lam root) root)
361 ) => Expr_from AST (Expr_Maybe lam root) where
362 expr_from ex ast ctx k =
363 case ast of
364 AST "maybe" asts -> from_ast3 asts maybe_from ex ast ctx k
365 AST "nothing" asts -> from_ast1 asts nothing_from ex ast ctx k
366 AST "just" asts -> from_ast1 asts just_from ex ast ctx k
367 _ -> Left $ error_expr_unsupported ex ast
368 instance -- Expr_from AST Expr_Eq
369 ( Type_from AST (Type_Root_of_Expr root)
370 , Type_Lift Type_Bool (Type_of_Expr root)
371 , Type_Constraint Eq (Type_Root_of_Expr root)
372 , Expr_from AST root
373 , Error_Expr_Lift (Error_Expr_of_Root AST root) (Error_of_Expr AST root)
374 , Root_of_Expr root ~ root
375 , Implicit_HBool (Is_Last_Expr (Expr_Eq root) root)
376 ) => Expr_from AST (Expr_Eq root) where
377 expr_from ex ast ctx k =
378 case ast of
379 AST "==" asts -> from_ast2 asts eq_from ex ast ctx k
380 _ -> Left $ error_expr_unsupported ex ast
381 instance -- Expr_from AST Expr_Ord
382 ( Type_from AST (Type_Root_of_Expr root)
383 , Type_Lift Type_Ordering (Type_of_Expr root)
384 , Type_Constraint Ord (Type_Root_of_Expr root)
385 , Expr_from AST root
386 , Error_Expr_Lift (Error_Expr_of_Root AST root) (Error_of_Expr AST root)
387 , Root_of_Expr root ~ root
388 , Implicit_HBool (Is_Last_Expr (Expr_Ord root) root)
389 ) => Expr_from AST (Expr_Ord root) where
390 expr_from ex ast ctx k =
391 case ast of
392 AST "compare" asts -> from_ast2 asts compare_from ex ast ctx k
393 _ -> Left $ error_expr_unsupported ex ast
394 instance -- Expr_from AST Expr_List
395 ( Type_from AST (Type_Root_of_Expr root)
396 , Expr_from AST root
397 , Type_Lift (Type_Fun lam) (Type_of_Expr root)
398 , Type_Unlift (Type_Fun lam) (Type_of_Expr root)
399 , Type_Lift Type_List (Type_of_Expr root)
400 , Type_Unlift Type_List (Type_of_Expr root)
401 , Type_Lift Type_Bool (Type_of_Expr root)
402 , Error_Expr_Lift (Error_Expr_of_Root AST root) (Error_of_Expr AST root)
403 , Root_of_Expr root ~ root
404 , Implicit_HBool (Is_Last_Expr (Expr_List lam root) root)
405 ) => Expr_from AST (Expr_List lam root) where
406 expr_from ex ast ctx k =
407 case ast of
408 AST "[]" asts -> from_ast1 asts list_empty_from ex ast ctx k
409 AST ":" asts -> from_ast2 asts list_cons_from ex ast ctx k
410 AST "list_filter" asts -> from_ast2 asts list_filter_from ex ast ctx k
411 _ -> Left $ error_expr_unsupported ex ast
412 instance -- Expr_from AST Expr_Map
413 ( Type_from AST (Type_Root_of_Expr root)
414 , Expr_from AST 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_Map (Type_of_Expr root)
418 , Type_Unlift Type_Map (Type_of_Expr root)
419 , Type_Lift Type_List (Type_of_Expr root)
420 , Type_Unlift Type_List (Type_of_Expr root)
421 , Type_Lift Type_Tuple2 (Type_of_Expr root)
422 , Type_Unlift Type_Tuple2 (Type_of_Expr root)
423 , Type_Constraint Ord (Type_Root_of_Expr root)
424 , Error_Expr_Lift (Error_Expr_of_Root AST root) (Error_of_Expr AST root)
425 , Root_of_Expr root ~ root
426 , Implicit_HBool (Is_Last_Expr (Expr_Map lam root) root)
427 ) => Expr_from AST (Expr_Map lam root) where
428 expr_from ex ast ctx k =
429 case ast of
430 AST "map_from_list" asts -> from_ast1 asts map_from_list_from ex ast ctx k
431 AST "map_map" asts -> from_ast2 asts map_map_from ex ast ctx k
432 _ -> Left $ error_expr_unsupported ex ast