]> 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 Prelude.<$> 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 , Lift_Error_Expr (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 , Lift_Error_Expr (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 , Lift_Error_Expr (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 , Lift_Error_Expr (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 , Lift_Error_Expr (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 , Eq_Type (Type_Root_of_Expr root)
133 , Expr_from ast root
134 , Lift_Error_Expr (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 , Eq_Type (Type_Root_of_Expr root)
152 , Expr_from ast root
153 , Lift_Error_Expr (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 ( Lift_Error_Type (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 ( Lift_Type_Root Type_Unit root
174 , Lift_Error_Type (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 $ lift_error_type $
183 Error_Type_Wrong_number_of_arguments ast 0
184 _ -> Left $ error_type_unsupported ty ast
185 instance -- Type_from AST Type_Bool
186 ( Lift_Type_Root Type_Bool root
187 , Lift_Error_Type (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 $ lift_error_type $
196 Error_Type_Wrong_number_of_arguments ast 0
197 _ -> Left $ error_type_unsupported ty ast
198 instance -- Type_from AST Type_Int
199 ( Lift_Type_Root Type_Int root
200 , Lift_Error_Type (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 $ lift_error_type $
209 Error_Type_Wrong_number_of_arguments ast 0
210 _ -> Left $ error_type_unsupported ty ast
211 instance -- Type_from AST Type_Ordering
212 ( Lift_Type_Root Type_Ordering root
213 , Lift_Error_Type (Error_Type AST) (Error_of_Type AST root)
214 , Implicit_HBool (Is_Last_Type (Type_Ordering root) root)
215 ) => Type_from AST (Type_Ordering root) where
216 type_from ty ast k =
217 case ast of
218 AST "Ordering" asts ->
219 case asts of
220 [] -> k type_ordering
221 _ -> Left $ lift_error_type $
222 Error_Type_Wrong_number_of_arguments ast 0
223 _ -> Left $ error_type_unsupported ty ast
224 instance -- Type_from AST Type_Fun
225 ( Eq_Type root
226 , Type_from AST root
227 , Lift_Type_Root (Type_Fun lam) root
228 , Lift_Error_Type (Error_Type AST) (Error_of_Type AST root)
229 , Unlift_Error_Type (Error_Type AST) (Error_of_Type AST root)
230 , Root_of_Type root ~ root
231 , Implicit_HBool (Is_Last_Type (Type_Fun lam root) root)
232 ) => Type_from AST (Type_Fun lam root) where
233 type_from ty ast k =
234 case ast of
235 AST "->" asts ->
236 case asts of
237 [ast_arg, ast_res] -> type_fun_from ty ast_arg ast_res k
238 _ -> Left $ lift_error_type $
239 Error_Type_Wrong_number_of_arguments ast 2
240 _ -> Left $ error_type_unsupported ty ast
241 instance -- Type_from AST Type_Maybe
242 ( Eq_Type root
243 , Type_from AST root
244 , Lift_Type_Root Type_Maybe root
245 , Lift_Error_Type (Error_Type AST) (Error_of_Type AST root)
246 , Unlift_Error_Type (Error_Type AST) (Error_of_Type AST root)
247 , Root_of_Type root ~ root
248 , Implicit_HBool (Is_Last_Type (Type_Maybe root) root)
249 ) => Type_from AST (Type_Maybe root) where
250 type_from ty ast k =
251 case ast of
252 AST "Maybe" asts ->
253 case asts of
254 [ast_a] ->
255 type_from (Proxy::Proxy root) ast_a $ \ty_a ->
256 k (type_maybe ty_a)
257 _ -> Left $ lift_error_type $
258 Error_Type_Wrong_number_of_arguments ast 1
259 _ -> Left $ error_type_unsupported ty ast
260 instance -- Type_from AST Type_List
261 ( Eq_Type root
262 , Type_from AST root
263 , Lift_Type_Root Type_List root
264 , Lift_Error_Type (Error_Type AST) (Error_of_Type AST root)
265 , Unlift_Error_Type (Error_Type AST) (Error_of_Type AST root)
266 , Root_of_Type root ~ root
267 , Implicit_HBool (Is_Last_Type (Type_List root) root)
268 ) => Type_from AST (Type_List root) where
269 type_from ty ast k =
270 case ast of
271 AST "[]" asts ->
272 case asts of
273 [ast_a] ->
274 type_from (Proxy::Proxy root) ast_a $ \ty_a ->
275 k (type_list ty_a)
276 _ -> Left $ lift_error_type $
277 Error_Type_Wrong_number_of_arguments ast 1
278 _ -> Left $ error_type_unsupported ty ast
279 instance -- Type1_from AST Type_Bool
280 ( Lift_Error_Type (Error_Type AST) (Error_of_Type AST root)
281 , Implicit_HBool (Is_Last_Type (Type_Bool root) root)
282 ) => Type1_from AST (Type_Bool root)
283 instance -- Type1_from AST Type_Int
284 ( Lift_Error_Type (Error_Type AST) (Error_of_Type AST root)
285 , Implicit_HBool (Is_Last_Type (Type_Int root) root)
286 ) => Type1_from AST (Type_Int root)
287 instance -- Type1_from AST Type_Unit
288 ( Lift_Error_Type (Error_Type AST) (Error_of_Type AST root)
289 , Implicit_HBool (Is_Last_Type (Type_Unit root) root)
290 ) => Type1_from AST (Type_Unit root)
291 instance -- Type1_from AST Type_Ordering
292 ( Lift_Error_Type (Error_Type AST) (Error_of_Type AST root)
293 , Implicit_HBool (Is_Last_Type (Type_Ordering root) root)
294 ) => Type1_from AST (Type_Ordering root)
295 instance -- Type1_from AST Type_Var
296 ( Lift_Error_Type (Error_Type AST) (Error_of_Type AST root)
297 , Implicit_HBool (Is_Last_Type (Type_Var root) root)
298 ) => Type1_from AST (Type_Var root)
299 instance -- Type1_from AST Type_Maybe
300 ( Type_from AST root
301 , Lift_Type_Root Type_Maybe root
302 , Lift_Error_Type (Error_Type AST) (Error_of_Type AST root)
303 , Unlift_Error_Type (Error_Type AST) (Error_of_Type AST root)
304 , Root_of_Type root ~ root
305 , Implicit_HBool (Is_Last_Type (Type_Maybe root) root)
306 ) => Type1_from AST (Type_Maybe root) where
307 type1_from ty ast k =
308 case ast of
309 AST "Maybe" asts ->
310 case asts of
311 [] -> k (Proxy::Proxy Maybe) type_maybe
312 _ -> Left $ lift_error_type $
313 Error_Type_Wrong_number_of_arguments ast 0
314 _ -> Left $ error_type_unsupported ty ast
315 instance -- Type1_from AST Type_List
316 ( Eq_Type root
317 , Type_from AST root
318 , Lift_Type_Root Type_List root
319 , Lift_Error_Type (Error_Type AST) (Error_of_Type AST root)
320 , Unlift_Error_Type (Error_Type AST) (Error_of_Type AST root)
321 , Root_of_Type root ~ root
322 , Implicit_HBool (Is_Last_Type (Type_List root) root)
323 ) => Type1_from AST (Type_List root) where
324 type1_from ty ast k =
325 case ast of
326 AST "[]" asts ->
327 case asts of
328 [] -> k (Proxy::Proxy []) type_list
329 _ -> Left $ lift_error_type $
330 Error_Type_Wrong_number_of_arguments ast 0
331 _ -> Left $ error_type_unsupported ty ast
332 instance -- Type1_from AST Type_Fun
333 ( Eq_Type root
334 , Type_from AST root
335 , Lift_Type_Root (Type_Fun lam) root
336 , Lift_Error_Type (Error_Type AST) (Error_of_Type AST root)
337 , Unlift_Error_Type (Error_Type AST) (Error_of_Type AST root)
338 , Root_of_Type root ~ root
339 , Implicit_HBool (Is_Last_Type (Type_Fun lam root) root)
340 ) => Type1_from AST (Type_Fun lam root) where
341 type1_from ty ast k =
342 case ast of
343 AST "->" asts ->
344 case asts of
345 [ast_arg] ->
346 type_from (Proxy::Proxy root) ast_arg $ \(ty_arg::root h_arg) ->
347 k (Proxy::Proxy (Lambda lam h_arg)) $
348 type_fun ty_arg
349 _ -> Left $ lift_error_type $
350 Error_Type_Wrong_number_of_arguments ast 1
351 _ -> Left $ error_type_unsupported ty ast
352 instance -- Expr_from AST Expr_Bool
353 ( Eq_Type (Type_Root_of_Expr root)
354 , Type_from AST (Type_Root_of_Expr root)
355 , Expr_from AST root
356 , Lift_Type_Root Type_Bool (Type_Root_of_Expr root)
357 , Lift_Error_Expr (Error_Expr_of_Root AST root) (Error_of_Expr AST root)
358 , Unlift_Type Type_Bool (Type_of_Expr root)
359 , Root_of_Expr root ~ root
360 , Implicit_HBool (Is_Last_Expr (Expr_Bool root) root)
361 ) => Expr_from AST (Expr_Bool root) where
362 expr_from ex ast =
363 case ast of
364 AST "bool" asts -> lit_from_AST bool type_bool asts ex ast
365 AST "not" asts -> op1_from_AST Expr.not type_bool asts ex ast
366 AST "&&" asts -> op2_from_AST (Expr.&&) type_bool asts ex ast
367 AST "||" asts -> op2_from_AST (Expr.||) type_bool asts ex ast
368 AST "xor" asts -> op2_from_AST Expr.xor type_bool asts ex ast
369 _ -> \_ctx _k -> Left $ error_expr_unsupported ex ast
370 instance -- Expr_from AST Expr_If
371 ( Eq_Type (Type_Root_of_Expr root)
372 , Type_from AST (Type_Root_of_Expr root)
373 , Expr_from AST root
374 , Lift_Type_Root Type_Bool (Type_Root_of_Expr root)
375 , Lift_Error_Expr (Error_Expr_of_Root AST root) (Error_of_Expr AST root)
376 , Root_of_Expr root ~ root
377 , Implicit_HBool (Is_Last_Expr (Expr_If root) root)
378 ) => Expr_from AST (Expr_If root) where
379 expr_from ex ast ctx k =
380 case ast of
381 AST "if" asts -> from_ast3 asts if_from ex ast ctx k
382 _ -> Left $ error_expr_unsupported ex ast
383 instance -- Expr_from AST Expr_When
384 ( Eq_Type (Type_Root_of_Expr root)
385 , Type_from AST (Type_Root_of_Expr root)
386 , Expr_from AST root
387 , Lift_Type_Root Type_Bool (Type_Root_of_Expr root)
388 , Lift_Type_Root Type_Unit (Type_Root_of_Expr root)
389 , Lift_Error_Expr (Error_Expr_of_Root AST root) (Error_of_Expr AST root)
390 , Root_of_Expr root ~ root
391 , Implicit_HBool (Is_Last_Expr (Expr_When root) root)
392 ) => Expr_from AST (Expr_When root) where
393 expr_from ex ast ctx k =
394 case ast of
395 AST "when" asts -> from_ast2 asts when_from ex ast ctx k
396 _ -> Left $ error_expr_unsupported ex ast
397 instance -- Expr_from AST Expr_Int
398 ( Eq_Type (Type_Root_of_Expr root)
399 , Type_from AST (Type_Root_of_Expr root)
400 , Expr_from AST root
401 , Lift_Type_Root Type_Int (Type_Root_of_Expr root)
402 , Lift_Error_Expr (Error_Expr_of_Root AST root) (Error_of_Expr AST root)
403 , Unlift_Type Type_Int (Type_of_Expr root)
404 , Root_of_Expr root ~ root
405 , Implicit_HBool (Is_Last_Expr (Expr_Int root) root)
406 ) => Expr_from AST (Expr_Int root) where
407 expr_from ex ast =
408 case ast of
409 AST "int" asts -> lit_from_AST int type_int asts ex ast
410 AST "abs" asts -> op1_from_AST Expr.abs type_int asts ex ast
411 AST "negate" asts -> op1_from_AST Expr.negate type_int asts ex ast
412 AST "+" asts -> op2_from_AST (Expr.+) type_int asts ex ast
413 AST "-" asts -> op2_from_AST (Expr.-) type_int asts ex ast
414 AST "*" asts -> op2_from_AST (Expr.*) type_int asts ex ast
415 AST "mod" asts -> op2_from_AST Expr.mod type_int asts ex ast
416 _ -> \_ctx _k -> Left $ error_expr_unsupported ex ast
417 instance -- Expr_from AST Expr_Lambda
418 ( Eq_Type (Type_Root_of_Expr root)
419 , Type_from AST (Type_Root_of_Expr root)
420 , Expr_from AST root
421 , Lift_Type_Root (Type_Fun lam) (Type_Root_of_Expr root)
422 , Lift_Error_Expr (Error_Expr_Lambda AST) (Error_of_Expr AST root)
423 , Lift_Error_Expr (Error_Expr_of_Root AST root) (Error_of_Expr AST root)
424 , Unlift_Type (Type_Fun lam) (Type_of_Expr root)
425 , Root_of_Expr root ~ root
426 , Implicit_HBool (Is_Last_Expr (Expr_Lambda lam root) root)
427 ) => Expr_from AST (Expr_Lambda lam root) where
428 expr_from ex ast ctx k =
429 case ast of
430 AST "var" asts ->
431 case asts of
432 [AST name []] -> var_from name ex ast ctx k
433 _ -> Left $ error_expr ex $
434 Error_Expr_Wrong_number_of_arguments ast 1
435 AST "app" asts -> from_ast2 asts app_from ex ast ctx k
436 AST "inline" asts -> go_lam asts inline
437 AST "val" asts -> go_lam asts val
438 AST "lazy" asts -> go_lam asts lazy
439 AST "let_inline" asts -> go_let asts let_inline
440 AST "let_val" asts -> go_let asts let_val
441 AST "let_lazy" asts -> go_let asts let_lazy
442 _ -> Left $ error_expr_unsupported ex ast
443 where
444 go_lam asts
445 (lam::forall repr arg res. Sym_Lambda lam repr
446 => (repr arg -> repr res) -> repr (Lambda lam arg res)) =
447 case asts of
448 [AST name [], ast_ty_arg, ast_body] ->
449 lam_from lam name ast_ty_arg ast_body ex ast ctx k
450 _ -> Left $ error_expr ex $
451 Error_Expr_Wrong_number_of_arguments ast 3
452 go_let asts
453 (let_::forall repr var res. Sym_Lambda lam repr
454 => repr var -> (repr var -> repr res) -> repr res) =
455 case asts of
456 [AST name [], ast_var, ast_body] ->
457 let_from let_ name ast_var ast_body ex ast ctx k
458 _ -> Left $ error_expr ex $
459 Error_Expr_Wrong_number_of_arguments ast 3
460 instance -- Expr_from AST Expr_Maybe
461 ( Eq_Type (Type_Root_of_Expr root)
462 , Type_from AST (Type_Root_of_Expr root)
463 , Expr_from AST root
464 , Lift_Type (Type_Fun lam) (Type_of_Expr root)
465 , Unlift_Type (Type_Fun lam) (Type_of_Expr root)
466 , Lift_Type Type_Maybe (Type_of_Expr root)
467 , Unlift_Type Type_Maybe (Type_of_Expr root)
468 , Lift_Error_Expr (Error_Expr_of_Root AST root) (Error_of_Expr AST root)
469 , Root_of_Expr root ~ root
470 , Implicit_HBool (Is_Last_Expr (Expr_Maybe lam root) root)
471 ) => Expr_from AST (Expr_Maybe lam root) where
472 expr_from ex ast ctx k =
473 case ast of
474 AST "maybe" asts -> from_ast3 asts maybe_from ex ast ctx k
475 AST "nothing" asts -> from_ast1 asts nothing_from ex ast ctx k
476 AST "just" asts -> from_ast1 asts just_from ex ast ctx k
477 _ -> Left $ error_expr_unsupported ex ast
478 instance -- Expr_from AST Expr_Eq
479 ( Eq_Type (Type_Root_of_Expr root)
480 , Type_from AST (Type_Root_of_Expr root)
481 , Lift_Type Type_Bool (Type_of_Expr root)
482 , Constraint_Type Eq (Type_Root_of_Expr root)
483 , Expr_from AST root
484 , Lift_Error_Expr (Error_Expr_of_Root AST root) (Error_of_Expr AST root)
485 , Root_of_Expr root ~ root
486 , Implicit_HBool (Is_Last_Expr (Expr_Eq root) root)
487 ) => Expr_from AST (Expr_Eq root) where
488 expr_from ex ast ctx k =
489 case ast of
490 AST "==" asts -> from_ast2 asts eq_from ex ast ctx k
491 _ -> Left $ error_expr_unsupported ex ast
492 instance -- Expr_from AST Expr_Ord
493 ( Eq_Type (Type_Root_of_Expr root)
494 , Type_from AST (Type_Root_of_Expr root)
495 , Lift_Type Type_Ordering (Type_of_Expr root)
496 , Constraint_Type Ord (Type_Root_of_Expr root)
497 , Expr_from AST root
498 , Lift_Error_Expr (Error_Expr_of_Root AST root) (Error_of_Expr AST root)
499 , Root_of_Expr root ~ root
500 , Implicit_HBool (Is_Last_Expr (Expr_Ord root) root)
501 ) => Expr_from AST (Expr_Ord root) where
502 expr_from ex ast ctx k =
503 case ast of
504 AST "compare" asts -> from_ast2 asts compare_from ex ast ctx k
505 _ -> Left $ error_expr_unsupported ex ast
506 instance -- Expr_from AST Expr_List
507 ( Eq_Type (Type_Root_of_Expr root)
508 , Type_from AST (Type_Root_of_Expr root)
509 , Expr_from AST root
510 , Lift_Type (Type_Fun lam) (Type_of_Expr root)
511 , Unlift_Type (Type_Fun lam) (Type_of_Expr root)
512 , Lift_Type Type_List (Type_of_Expr root)
513 , Unlift_Type Type_List (Type_of_Expr root)
514 , Lift_Type Type_Bool (Type_of_Expr root)
515 , Lift_Error_Expr (Error_Expr_of_Root AST root) (Error_of_Expr AST root)
516 , Root_of_Expr root ~ root
517 , Implicit_HBool (Is_Last_Expr (Expr_List lam root) root)
518 ) => Expr_from AST (Expr_List lam root) where
519 expr_from ex ast ctx k =
520 case ast of
521 AST "[]" asts -> from_ast1 asts list_empty_from ex ast ctx k
522 AST ":" asts -> from_ast2 asts list_cons_from ex ast ctx k
523 AST "list_filter" asts -> from_ast2 asts list_filter_from ex ast ctx k
524 AST "list" asts ->
525 case asts of
526 ast_ty_a:asts' -> list_from ast_ty_a asts' ex ast ctx k
527 _ -> Left $ error_expr ex $
528 Error_Expr_Wrong_number_of_arguments ast 1
529 _ -> Left $ error_expr_unsupported ex ast
530 instance -- Expr_from AST Expr_Map
531 ( Eq_Type (Type_Root_of_Expr root)
532 , Type_from AST (Type_Root_of_Expr root)
533 , Expr_from AST root
534 , Lift_Type (Type_Fun lam) (Type_of_Expr root)
535 , Unlift_Type (Type_Fun lam) (Type_of_Expr root)
536 , Lift_Type Type_Map (Type_of_Expr root)
537 , Unlift_Type Type_Map (Type_of_Expr root)
538 , Lift_Type Type_List (Type_of_Expr root)
539 , Unlift_Type Type_List (Type_of_Expr root)
540 , Lift_Type Type_Tuple2 (Type_of_Expr root)
541 , Unlift_Type Type_Tuple2 (Type_of_Expr root)
542 , Constraint_Type Ord (Type_Root_of_Expr root)
543 , Lift_Error_Expr (Error_Expr_of_Root AST root) (Error_of_Expr AST root)
544 , Root_of_Expr root ~ root
545 , Implicit_HBool (Is_Last_Expr (Expr_Map lam root) root)
546 ) => Expr_from AST (Expr_Map lam root) where
547 expr_from ex ast ctx k =
548 case ast of
549 AST "map_from_list" asts -> from_ast1 asts map_from_list_from ex ast ctx k
550 AST "map_map" asts -> from_ast2 asts map_map_from ex ast ctx k
551 _ -> Left $ error_expr_unsupported ex ast
552 instance -- Expr_from AST Expr_Functor
553 ( Eq_Type (Type_Root_of_Expr root)
554 , Type_from AST (Type_Root_of_Expr root)
555 , Expr_from AST root
556 , String_from_Type (Type_Root_of_Expr root)
557 , Lift_Type (Type_Fun lam) (Type_of_Expr root)
558 , Unlift_Type (Type_Fun lam) (Type_of_Expr root)
559 , Unlift_Type1 (Type_of_Expr root)
560 , Lift_Error_Expr (Error_Expr_of_Root AST root) (Error_of_Expr AST root)
561 , Constraint_Type1 Functor_with_Lambda (Type_Root_of_Expr root)
562 , Root_of_Expr root ~ root
563 , Implicit_HBool (Is_Last_Expr (Expr_Functor lam root) root)
564 ) => Expr_from AST (Expr_Functor lam root) where
565 expr_from ex ast ctx k =
566 case ast of
567 AST "fmap" asts -> from_ast2 asts fmap_from ex ast ctx k
568 AST "<$>" asts -> from_ast2 asts fmap_from ex ast ctx k
569 _ -> Left $ error_expr_unsupported ex ast
570 instance -- Expr_from AST Expr_Applicative
571 ( Eq_Type (Type_Root_of_Expr root)
572 , Type1_from AST (Type_Root_of_Expr root)
573 , Expr_from AST root
574 , String_from_Type (Type_Root_of_Expr root)
575 , Lift_Type (Type_Fun lam) (Type_of_Expr root)
576 , Unlift_Type (Type_Fun lam) (Type_of_Expr root)
577 , Eq_Type1 (Type_Root_of_Expr root)
578 , Unlift_Type1 (Type_of_Expr root)
579 , Lift_Error_Expr (Error_Expr_of_Root AST root) (Error_of_Expr AST root)
580 , Constraint_Type1 Applicative_with_Lambda (Type_Root_of_Expr root)
581 , Root_of_Expr root ~ root
582 , Implicit_HBool (Is_Last_Expr (Expr_Applicative lam root) root)
583 ) => Expr_from AST (Expr_Applicative lam root) where
584 expr_from ex ast ctx k =
585 case ast of
586 AST "pure" asts -> from_ast2 asts pure_from ex ast ctx k
587 AST "<*>" asts -> from_ast2 asts ltstargt_from ex ast ctx k
588 _ -> Left $ error_expr_unsupported ex ast