]> Git — Sourcephile - haskell/symantic.git/blob - Language/Symantic/Type/Common.hs
init
[haskell/symantic.git] / Language / Symantic / Type / Common.hs
1 {-# LANGUAGE ConstraintKinds #-}
2 {-# LANGUAGE DataKinds #-}
3 {-# LANGUAGE DefaultSignatures #-}
4 {-# LANGUAGE ExistentialQuantification #-}
5 {-# LANGUAGE FlexibleContexts #-}
6 {-# LANGUAGE FlexibleInstances #-}
7 {-# LANGUAGE GADTs #-}
8 {-# LANGUAGE MultiParamTypeClasses #-}
9 {-# LANGUAGE Rank2Types #-}
10 {-# LANGUAGE ScopedTypeVariables #-}
11 {-# LANGUAGE TypeFamilies #-}
12 {-# LANGUAGE TypeOperators #-}
13 {-# LANGUAGE UndecidableInstances #-}
14 module Language.Symantic.Type.Common where
15
16 import Data.Maybe (isJust, fromMaybe)
17 import Data.Proxy
18 import Data.Type.Equality ((:~:)(Refl))
19 import Language.Symantic.Lib.Data.Peano
20 import GHC.Prim (Constraint)
21
22 -- * Class 'Eq_Type'
23 -- | Test two types for equality,
24 -- returning an Haskell type-level proof
25 -- of the equality when it holds.
26 class Eq_Type (ty:: * -> *) where
27 eq_type :: forall h1 h2. ty h1 -> ty h2 -> Maybe (h1 :~: h2)
28
29 -- * Class 'Eq_Type1'
30 -- | Test two type constructors for equality,
31 -- returning an Haskell type-level proof
32 -- of the equality when it holds.
33 class Eq_Type1 (ty:: * -> *) where
34 eq_type1 :: forall h1 h2 a1 a2. ty (h1 a1) -> ty (h2 a2) -> Maybe (h1 :~: h2)
35 eq_type1 = error "eq_type1"
36
37 -- * Class 'Constraint_Type'
38 -- | Test if a type satisfies a given 'Constraint',
39 -- returning an Haskell type-level proof
40 -- of that satisfaction when it holds.
41 class Constraint_Type (c:: * -> Constraint) (ty:: * -> *) where
42 constraint_type :: forall h. Proxy c -> ty h -> Maybe (Dict (c h))
43 constraint_type _c _ = Nothing
44
45 -- * Class 'Constraint_Type1'
46 -- | Test if a type constructor satisfies a given 'Constraint',
47 -- returning an Haskell type-level proof
48 -- of that satisfaction when it holds.
49 class Constraint_Type1 (c:: (* -> *) -> Constraint) (ty:: * -> *) where
50 constraint_type1 :: forall h1 h. Proxy c -> ty (h1 h) -> Maybe (Dict (c h1))
51 constraint_type1 _c _ = Nothing
52
53 -- ** Type 'Dict'
54 -- | 'Dict' captures the dictionary of a 'Constraint':
55 -- pattern matching on the 'Dict' constructor
56 -- brings the 'Constraint' into scope.
57 data Dict :: Constraint -> * where
58 Dict :: c => Dict c
59
60 -- * Type 'Exists_Dict'
61 data Exists_Dict
62 = forall c. Exists_Dict (Dict c)
63
64 -- * Class 'Type_from'
65 -- | Parse given @ast@ into a 'Root_of_Type',
66 -- or return an 'Error_of_Type'.
67 --
68 -- NOTE: making a distinction between @ty@ and 'Root_of_Type'@ ty@,
69 -- instead of having only a @root@ variable
70 -- is what enables to define many instances, one per type.
71 class Type_from ast (ty:: * -> *) where
72 type_from
73 :: Proxy ty
74 -> ast
75 -> (forall h. Root_of_Type ty h
76 -> Either (Error_of_Type ast (Root_of_Type ty)) ret)
77 -> Either (Error_of_Type ast (Root_of_Type ty)) ret
78
79 -- * Class 'Type1_from'
80 -- | Parse given @ast@ into a 'Root_of_Type' constructor,
81 -- or return an 'Error_of_Type'.
82 class Type1_from ast (ty:: * -> *) where
83 type1_from
84 :: Proxy ty
85 -> ast
86 -> (forall (f:: * -> *). Proxy f
87 -> (forall h. Root_of_Type ty h -> Root_of_Type ty (f h))
88 -> Either (Error_of_Type ast (Root_of_Type ty)) ret)
89 -> Either (Error_of_Type ast (Root_of_Type ty)) ret
90 default type1_from ::
91 ( Lift_Error_Type (Error_Type ast) (Error_of_Type ast (Root_of_Type ty))
92 , Implicit_HBool (Is_Last_Type ty (Root_of_Type ty))
93 ) => Proxy ty
94 -> ast
95 -> (forall (f:: * -> *). Proxy f
96 -> (forall h. Root_of_Type ty h -> Root_of_Type ty (f h))
97 -> Either (Error_of_Type ast (Root_of_Type ty)) ret)
98 -> Either (Error_of_Type ast (Root_of_Type ty)) ret
99 type1_from ty ast _k =
100 Left $ error_type_unsupported ty ast
101
102 {-
103 class Type1_f_from (ty:: * -> *) where
104 type1_f_from
105 :: Proxy ty
106 -> (Root_of_Type ty) h_any
107 -> (forall (f:: * -> *). Proxy f
108 -> (forall h. (Root_of_Type ty) h -> (Root_of_Type ty) (f h))
109 -> Either ({-Error_of_Type ast (Root_of_Type ty)-}) ret)
110 -> Either ({-Error_of_Type ast (Root_of_Type ty)-}) ret
111 instance -- Type1_f_from
112 ( Eq_Type (curr root)
113 , Type1_f_from ast (curr root)
114 , Type1_f_from ast (next root)
115 , Root_of_Type (curr root) ~ root
116 , Root_of_Type (next root) ~ root
117 -- , Unlift_Error_Type (Error_Type ast) (Error_of_Type ast root)
118 ) => Type1_from ast (Type_Alt curr next root) where
119 type1_from _ty ast k =
120 case type1_from (Proxy::Proxy (curr root)) ast (\f ty -> Right $ k f ty) of
121 Right ret -> ret
122 Left err ->
123 case unlift_error_type err of
124 Just (Error_Type_Unsupported_here (_::ast)) ->
125 type1_from (Proxy::Proxy (next root)) ast k
126 _ -> Left err
127 -}
128
129 -- ** Type family 'Root_of_Type'
130 -- | Return the root type of a type.
131 type family Root_of_Type (ty:: * -> *) :: * -> *
132
133 -- ** Type family 'Error_of_Type'
134 -- | Return the error type of a type.
135 type family Error_of_Type (ast:: *) (ty:: * -> *) :: *
136
137 -- * Type 'No_Type'
138 -- | A discarded type.
139 data No_Type (root:: * -> *) h
140 = No_Type (root h)
141 deriving (Eq, Show)
142
143 -- * Type 'Type_Root'
144 -- | The root type, passing itself as parameter to the given type.
145 newtype Type_Root (ty:: (* -> *) -> * -> *) h
146 = Type_Root { unType_Root :: ty (Type_Root ty) h }
147 type instance Root_of_Type (Type_Root ty) = Type_Root ty
148 -- type instance Root_of_Type (ty (Type_Root ty)) = Type_Root ty
149 type instance Error_of_Type ast (Type_Root ty)
150 = Error_Type_Alt (Error_Type ast)
151 (Error_of_Type ast (ty (Type_Root ty)))
152 instance -- Eq_Type
153 Eq_Type (ty (Type_Root ty)) =>
154 Eq_Type (Type_Root ty) where
155 eq_type (Type_Root x) (Type_Root y) = x `eq_type` y
156 instance -- Eq_Type1
157 Eq_Type1 (ty (Type_Root ty)) =>
158 Eq_Type1 (Type_Root ty) where
159 eq_type1 (Type_Root x) (Type_Root y) = x `eq_type1` y
160 instance -- Eq
161 Eq_Type (Type_Root ty) =>
162 Eq (Type_Root ty h) where
163 x == y = isJust $ x `eq_type` y
164 instance -- Constraint_Type c Type_Root
165 Constraint_Type c (ty (Type_Root ty)) =>
166 Constraint_Type c (Type_Root ty) where
167 constraint_type c (Type_Root ty) = constraint_type c ty
168 instance -- Constraint_Type1 c Type_Root
169 Constraint_Type1 c (ty (Type_Root ty)) =>
170 Constraint_Type1 c (Type_Root ty) where
171 constraint_type1 c (Type_Root ty) = constraint_type1 c ty
172 instance -- Type_from
173 ( Eq_Type (Type_Root ty)
174 , Type_from ast (ty (Type_Root ty))
175 , Root_of_Type (ty (Type_Root ty)) ~ Type_Root ty
176 ) => Type_from ast (Type_Root ty) where
177 type_from _ty = type_from (Proxy::Proxy (ty (Type_Root ty)))
178 instance -- Type1_from
179 ( Eq_Type (Type_Root ty)
180 , Type1_from ast (ty (Type_Root ty))
181 , Root_of_Type (ty (Type_Root ty)) ~ Type_Root ty
182 ) => Type1_from ast (Type_Root ty) where
183 type1_from _ty = type1_from (Proxy::Proxy (ty (Type_Root ty)))
184 instance -- String_from_Type
185 String_from_Type (ty (Type_Root ty)) =>
186 String_from_Type (Type_Root ty) where
187 string_from_type (Type_Root ty) = string_from_type ty
188 instance -- Show
189 String_from_Type (Type_Root ty) =>
190 Show (Type_Root ty h) where
191 show = string_from_type
192
193 -- ** Class 'Lift_Type_Root'
194 -- | Lift a given type to a given root type.
195 class Lift_Type_Root ty root where
196 lift_type_root :: forall h. ty root h -> root h
197 instance
198 Lift_Type ty root =>
199 Lift_Type_Root ty (Type_Root root) where
200 lift_type_root = Type_Root . lift_type
201
202 -- * Type 'Type_Alt'
203 -- | Type making an alternative between two types.
204 data Type_Alt curr next (root:: * -> *) h
205 = Type_Alt_Curr (curr root h)
206 | Type_Alt_Next (next root h)
207 -- | Convenient alias. Requires @TypeOperators@.
208 type (:|:) = Type_Alt
209 infixr 5 :|:
210 type instance Root_of_Type (Type_Alt curr next root) = root
211 type instance Error_of_Type ast (Type_Alt curr next root)
212 = Error_of_Type_Alt ast (Error_of_Type ast (curr root))
213 (Error_of_Type ast (next root))
214 -- ** Type family 'Error_of_Type_Alt'
215 -- | Remove 'No_Error_Type' type when building 'Error_of_Type'.
216 type family Error_of_Type_Alt ast curr next where
217 Error_of_Type_Alt ast curr No_Error_Type = curr
218 Error_of_Type_Alt ast No_Error_Type next = next
219 Error_of_Type_Alt ast curr next = Error_Type_Alt curr next
220
221 -- ** Type 'No_Error_Type'
222 -- | A discarded error.
223 data No_Error_Type
224 = No_Error_Type
225 deriving (Eq, Show)
226
227 instance -- Eq_Type
228 ( Eq_Type (curr root)
229 , Eq_Type (next root)
230 ) => Eq_Type (Type_Alt curr next root) where
231 eq_type (Type_Alt_Curr x) (Type_Alt_Curr y) = x `eq_type` y
232 eq_type (Type_Alt_Next x) (Type_Alt_Next y) = x `eq_type` y
233 eq_type _ _ = Nothing
234 instance -- Eq_Type1
235 ( Eq_Type1 (curr root)
236 , Eq_Type1 (next root)
237 ) => Eq_Type1 (Type_Alt curr next root) where
238 eq_type1 (Type_Alt_Curr x) (Type_Alt_Curr y) = x `eq_type1` y
239 eq_type1 (Type_Alt_Next x) (Type_Alt_Next y) = x `eq_type1` y
240 eq_type1 _ _ = Nothing
241 instance -- Eq
242 ( Eq_Type (curr root)
243 , Eq_Type (next root)
244 ) => Eq (Type_Alt curr next root h) where
245 x == y = isJust $ x `eq_type` y
246 instance -- Constraint_Type c Type_Alt
247 ( Constraint_Type c (curr root)
248 , Constraint_Type c (next root)
249 ) => Constraint_Type c (Type_Alt curr next root) where
250 constraint_type c (Type_Alt_Curr ty) = constraint_type c ty
251 constraint_type c (Type_Alt_Next ty) = constraint_type c ty
252 instance -- Constraint_Type1 c Type_Alt
253 ( Constraint_Type1 c (curr root)
254 , Constraint_Type1 c (next root)
255 ) => Constraint_Type1 c (Type_Alt curr next root) where
256 constraint_type1 c (Type_Alt_Curr ty) = constraint_type1 c ty
257 constraint_type1 c (Type_Alt_Next ty) = constraint_type1 c ty
258 instance -- Type_from
259 ( Eq_Type (curr root)
260 , Type_from ast (curr root)
261 , Type_from ast (next root)
262 , Root_of_Type (curr root) ~ root
263 , Root_of_Type (next root) ~ root
264 , Unlift_Error_Type (Error_Type ast) (Error_of_Type ast root)
265 ) => Type_from ast (Type_Alt curr next root) where
266 type_from _ty ast k =
267 case type_from (Proxy::Proxy (curr root)) ast (Right . k) of
268 Right ret -> ret
269 Left err ->
270 case unlift_error_type err of
271 Just (Error_Type_Unsupported_here (_::ast)) ->
272 type_from (Proxy::Proxy (next root)) ast k
273 _ -> Left err
274 instance -- Type1_from
275 ( Eq_Type (curr root)
276 , Type1_from ast (curr root)
277 , Type1_from ast (next root)
278 , Root_of_Type (curr root) ~ root
279 , Root_of_Type (next root) ~ root
280 , Unlift_Error_Type (Error_Type ast) (Error_of_Type ast root)
281 ) => Type1_from ast (Type_Alt curr next root) where
282 type1_from _ty ast k =
283 case type1_from (Proxy::Proxy (curr root)) ast (\f ty -> Right $ k f ty) of
284 Right ret -> ret
285 Left err ->
286 case unlift_error_type err of
287 Just (Error_Type_Unsupported_here (_::ast)) ->
288 type1_from (Proxy::Proxy (next root)) ast k
289 _ -> Left err
290 instance -- String_from_Type
291 ( String_from_Type (curr root)
292 , String_from_Type (next root)
293 ) => String_from_Type (Type_Alt curr next root) where
294 string_from_type (Type_Alt_Curr t) = string_from_type t
295 string_from_type (Type_Alt_Next t) = string_from_type t
296
297 -- * Type 'Type_Type0'
298 data Type_Type0 t0 (root:: * -> *) h where
299 Type_Type0 :: Proxy t0 -> Type_Type0 t0 root t0
300
301 type instance Root_of_Type (Type_Type0 t0 root) = root
302 type instance Error_of_Type ast (Type_Type0 t0 root) = No_Error_Type
303
304 instance -- Eq_Type
305 Eq_Type (Type_Type0 t0 root) where
306 eq_type Type_Type0{} Type_Type0{} = Just Refl
307 instance -- Eq
308 Eq (Type_Type0 t0 root h) where
309 x == y = isJust $ x `eq_type` y
310 instance -- Show
311 String_from_Type (Type_Type0 t0 root) =>
312 Show (Type_Type0 t0 root h) where
313 show = string_from_type
314 instance Eq t0 => Constraint_Type Eq (Type_Type0 t0 root) where
315 constraint_type _c Type_Type0{} = Just Dict
316 instance Ord t0 => Constraint_Type Ord (Type_Type0 t0 root) where
317 constraint_type _c Type_Type0{} = Just Dict
318 instance Unlift_Type1 (Type_Type0 t0)
319 instance Eq_Type1 (Type_Type0 t0 root)
320
321 -- | Convenient alias to include a 'Type_Bool' within a type.
322 type_type0 :: Lift_Type_Root (Type_Type0 t0) root => root t0
323 type_type0 = lift_type_root (Type_Type0 Proxy)
324
325 -- ** Type 'Lift_Type'
326 -- | Apply 'Peano_of_Type' on 'Lift_TypeP'.
327 type Lift_Type ty tys
328 = Lift_TypeP (Peano_of_Type ty tys) ty tys
329
330 -- *** Type 'Peano_of_Type'
331 -- | Return a 'Peano' number derived from the location
332 -- of a given type within a given type stack,
333 -- which is used to avoid @OverlappingInstances@.
334 type family Peano_of_Type
335 (ty:: (* -> *) -> * -> *)
336 (tys:: (* -> *) -> * -> *) :: * where
337 Peano_of_Type ty ty = Zero
338 Peano_of_Type ty (Type_Alt ty next) = Zero
339 Peano_of_Type other (Type_Alt curr next) = Succ (Peano_of_Type other next)
340
341 -- *** Class 'Lift_TypeP'
342 -- | Lift a given type to the top of a given type stack including it,
343 -- by constructing the appropriate sequence of 'Type_Alt_Curr' and 'Type_Alt_Next'.
344 class Lift_TypeP (p:: *) ty tys where
345 lift_typeP :: forall (root:: * -> *) h. Proxy p -> ty root h -> tys root h
346 instance Lift_TypeP Zero curr curr where
347 lift_typeP _ = id
348 instance Lift_TypeP Zero curr (Type_Alt curr next) where
349 lift_typeP _ = Type_Alt_Curr
350 instance
351 Lift_TypeP p other next =>
352 Lift_TypeP (Succ p) other (Type_Alt curr next) where
353 lift_typeP _ = Type_Alt_Next . lift_typeP (Proxy::Proxy p)
354
355 -- | Convenient wrapper around 'lift_typeP',
356 -- passing it the 'Peano' number from 'Peano_of_Type'.
357 lift_type
358 :: forall ty tys (root:: * -> *) h.
359 Lift_Type ty tys =>
360 ty root h -> tys root h
361 lift_type = lift_typeP (Proxy::Proxy (Peano_of_Type ty tys))
362
363 -- ** Type 'Unlift_Type'
364 -- | Apply 'Peano_of_Type' on 'Unlift_TypeP'.
365 type Unlift_Type ty tys
366 = Unlift_TypeP (Peano_of_Type ty tys) ty tys
367
368 -- *** Class 'Unlift_TypeP'
369 -- | Try to unlift a given type out of a given type stack including it,
370 -- by deconstructing the appropriate sequence of 'Type_Alt_Curr' and 'Type_Alt_Next'.
371 class Unlift_TypeP (p:: *) ty tys where
372 type_unliftN :: forall (root:: * -> *) h. Proxy p -> tys root h -> Maybe (ty root h)
373 instance Unlift_TypeP Zero curr curr where
374 type_unliftN _ = Just
375 instance Unlift_TypeP Zero curr (Type_Alt curr next) where
376 type_unliftN _ (Type_Alt_Curr x) = Just x
377 type_unliftN _ (Type_Alt_Next _) = Nothing
378 instance
379 Unlift_TypeP p other next =>
380 Unlift_TypeP (Succ p) other (Type_Alt curr next) where
381 type_unliftN _ (Type_Alt_Next x) = type_unliftN (Proxy::Proxy p) x
382 type_unliftN _ (Type_Alt_Curr _) = Nothing
383
384 -- | Convenient wrapper around 'type_unliftN',
385 -- passing it the 'Peano' number from 'Peano_of_Type'.
386 unlift_type
387 :: forall ty tys (root:: * -> *) h.
388 Unlift_Type ty tys =>
389 tys root h -> Maybe (ty root h)
390 unlift_type = type_unliftN (Proxy::Proxy (Peano_of_Type ty tys))
391
392 -- * Type 'Type_Type1'
393 data Type_Type1 f (root:: * -> *) h where
394 Type_Type1 :: Proxy f -> root a -> Type_Type1 f root (f a)
395 type instance Root_of_Type (Type_Type1 f root) = root
396 type instance Error_of_Type ast (Type_Type1 f root) = No_Error_Type
397
398 instance Constraint_Type Eq (Type_Type1 f root)
399 instance Constraint_Type Ord (Type_Type1 f root)
400
401 instance -- Eq_Type
402 Eq_Type root =>
403 Eq_Type (Type_Type1 f root) where
404 eq_type (Type_Type1 _f1 a1) (Type_Type1 _f2 a2)
405 | Just Refl <- a1 `eq_type` a2
406 = Just Refl
407 eq_type _ _ = Nothing
408 instance -- Eq_Type1
409 Eq_Type1 root =>
410 Eq_Type1 (Type_Type1 f root) where
411 eq_type1 Type_Type1{} Type_Type1{}
412 = Just Refl
413 instance -- Eq
414 Eq_Type root =>
415 Eq (Type_Type1 f root h) where
416 x == y = isJust $ eq_type x y
417 instance -- Show
418 String_from_Type (Type_Type1 f root) =>
419 Show (Type_Type1 f root h) where
420 show = string_from_type
421
422 -- ** Type family 'May_be_Type1'
423 type family May_be_Type1
424 (ty:: (* -> *) -> * -> *) :: Bool where
425 May_be_Type1 (Type_Type1 f) = 'True
426 May_be_Type1 (Type_Alt (Type_Type1 f) next) = 'True
427 May_be_Type1 (Type_Alt curr next) = May_be_Type1 next
428 May_be_Type1 ty = 'False
429
430 -- ** Type 'Lift_Type1'
431 data Lift_Type1 f tys
432 = Lift_Type1 ( forall (root:: * -> *) h
433 . Type_Type1 f root h -> tys root h
434 )
435
436 -- ** Type 'Unlift_Type1'
437 class Unlift_Type1 ty where
438 unlift_type1
439 :: forall (root:: * -> *) ret h.
440 ty root h
441 -> (forall (f:: * -> *).
442 ( Type_Type1 f root h
443 , Lift_Type1 f ty
444 ) -> Maybe ret)
445 -> Maybe ret
446 unlift_type1 _ty _k = Nothing
447 instance Unlift_Type1 (Type_Type1 f) where
448 unlift_type1 ty k = k (ty, Lift_Type1 id)
449 instance -- Type_Alt
450 ( Unlift_Type1 curr
451 , Unlift_Type1 next
452 ) => Unlift_Type1 (Type_Alt curr next) where
453 unlift_type1 (Type_Alt_Curr ty) k =
454 fromMaybe Nothing $ unlift_type1 ty $ \(t, Lift_Type1 l) ->
455 Just $ k (t, Lift_Type1 $ Type_Alt_Curr . l)
456 unlift_type1 (Type_Alt_Next ty) k =
457 fromMaybe Nothing $ unlift_type1 ty $ \(t, Lift_Type1 l) ->
458 Just $ k (t, Lift_Type1 $ Type_Alt_Next . l)
459
460 -- * Type 'Type_Type2'
461 data Type_Type2 c2 t2 (root:: * -> *) h where
462 Type_Type2 :: c2 a b => Proxy c2 -> Proxy t2 -> root a -> root b -> Type_Type2 c2 t2 root (t2 a b)
463 class Constraint2_Empty a b
464 instance Constraint2_Empty a b
465
466 type instance Root_of_Type (Type_Type2 c2 t2 root) = root
467 type instance Error_of_Type ast (Type_Type2 c2 t2 root) = No_Error_Type
468
469 instance -- Eq_Type
470 Eq_Type root =>
471 Eq_Type (Type_Type2 c2 t2 root) where
472 eq_type
473 (Type_Type2 _ _ arg1 res1)
474 (Type_Type2 _ _ arg2 res2)
475 | Just Refl <- arg1 `eq_type` arg2
476 , Just Refl <- res1 `eq_type` res2
477 = Just Refl
478 eq_type _ _ = Nothing
479 instance -- Eq
480 Eq_Type root =>
481 Eq (Type_Type2 c2 t2 root h) where
482 x == y = isJust $ x `eq_type` y
483 instance -- Show
484 ( String_from_Type root
485 , String_from_Type (Type_Type2 c2 t2 root)
486 ) => Show (Type_Type2 c2 t2 root h) where
487 show = string_from_type
488 instance Constraint_Type Eq (Type_Type2 c2 t2 root)
489 instance Constraint_Type Ord (Type_Type2 c2 t2 root)
490 instance Unlift_Type1 (Type_Type2 c2 t2) -- FIXME: should be doable
491 instance Eq_Type1 (Type_Type2 c2 t2 root) -- FIXME: should be doable
492
493 -- * Type family 'Is_Last_Type'
494 -- | Return whether a given type is the last one in a given type stack.
495 --
496 -- NOTE: each type parser uses this type family
497 -- when it encounters unsupported syntax:
498 -- to know if it is the last type parser component that will be tried
499 -- (and thus return 'Error_Type_Unsupported')
500 -- or if some other type parser component shall be tried
501 -- (and thus return 'Error_Type_Unsupported_here',
502 -- which is then handled accordingly by the 'Type_from' instance of 'Type_Alt').
503 type family Is_Last_Type (ty:: * -> *) (tys:: * -> *) :: Bool where
504 Is_Last_Type ty ty = 'True
505 Is_Last_Type ty (Type_Root tys) = Is_Last_Type ty (tys (Type_Root tys))
506 Is_Last_Type (ty root) (Type_Alt ty next root) = 'False
507 Is_Last_Type other (Type_Alt curr next root) = Is_Last_Type other (next root)
508
509 -- * Type 'Error_Type_Alt'
510 -- | Error type making an alternative between two error types.
511 data Error_Type_Alt curr next
512 = Error_Type_Alt_Curr curr
513 | Error_Type_Alt_Next next
514 deriving (Eq, Show)
515
516 -- ** Type 'Lift_Error_Type'
517 type Lift_Error_Type err errs
518 = Lift_Error_TypeP (Peano_of_Error_Type err errs) err errs
519
520 -- *** Type 'Peano_of_Error_Type'
521 -- | Return a 'Peano' number derived from the location
522 -- of a given error type within a given error type stack.
523 type family Peano_of_Error_Type (err:: *) (errs:: *) :: * where
524 Peano_of_Error_Type err err = Zero
525 Peano_of_Error_Type err (Error_Type_Alt err next) = Zero
526 Peano_of_Error_Type other (Error_Type_Alt curr next) = Succ (Peano_of_Error_Type other next)
527
528 -- *** Class 'Lift_Error_TypeP'
529 -- | Lift a given error type to the top of a given error type stack including it,
530 -- by constructing the appropriate sequence of 'Error_Type_Alt_Curr' and 'Error_Type_Alt_Next'.
531 class Lift_Error_TypeP (p:: *) err errs where
532 lift_error_typeP :: Proxy p -> err -> errs
533 instance Lift_Error_TypeP Zero curr curr where
534 lift_error_typeP _ = id
535 instance Lift_Error_TypeP Zero curr (Error_Type_Alt curr next) where
536 lift_error_typeP _ = Error_Type_Alt_Curr
537 instance
538 Lift_Error_TypeP p other next =>
539 Lift_Error_TypeP (Succ p) other (Error_Type_Alt curr next) where
540 lift_error_typeP _ = Error_Type_Alt_Next . lift_error_typeP (Proxy::Proxy p)
541
542 -- | Convenient wrapper around 'error_type_unliftN',
543 -- passing it the 'Peano' number from 'Peano_of_Error_Type'.
544 lift_error_type
545 :: forall err errs.
546 Lift_Error_Type err errs =>
547 err -> errs
548 lift_error_type = lift_error_typeP (Proxy::Proxy (Peano_of_Error_Type err errs))
549
550 -- ** Type 'Unlift_Error_Type'
551 -- | Apply 'Peano_of_Error_Type' on 'Error_Type_UnliftN'.
552 type Unlift_Error_Type ty tys
553 = Error_Type_UnliftN (Peano_of_Error_Type ty tys) ty tys
554
555 -- | Convenient wrapper around 'error_type_unliftN',
556 -- passing it the 'Peano' number from 'Peano_of_Error_Type'.
557 unlift_error_type
558 :: forall ty tys.
559 Unlift_Error_Type ty tys =>
560 tys -> Maybe ty
561 unlift_error_type = error_type_unliftN (Proxy::Proxy (Peano_of_Error_Type ty tys))
562
563 -- *** Class 'Error_Type_UnliftN'
564 -- | Try to unlift a given type error out of a given type error stack including it,
565 -- by deconstructing the appropriate sequence of 'Error_Type_Alt_Curr' and 'Error_Type_Alt_Next'.
566 class Error_Type_UnliftN (p:: *) ty tys where
567 error_type_unliftN :: Proxy p -> tys -> Maybe ty
568 instance Error_Type_UnliftN Zero curr curr where
569 error_type_unliftN _ = Just
570 instance Error_Type_UnliftN Zero curr (Error_Type_Alt curr next) where
571 error_type_unliftN _ (Error_Type_Alt_Curr x) = Just x
572 error_type_unliftN _ (Error_Type_Alt_Next _) = Nothing
573 instance
574 Error_Type_UnliftN p other next =>
575 Error_Type_UnliftN (Succ p) other (Error_Type_Alt curr next) where
576 error_type_unliftN _ (Error_Type_Alt_Next x) = error_type_unliftN (Proxy::Proxy p) x
577 error_type_unliftN _ (Error_Type_Alt_Curr _) = Nothing
578
579 -- ** Type 'Error_Type_Read'
580 -- | Common type errors.
581 data Error_Type ast
582 = Error_Type_Unsupported ast
583 -- ^ Given syntax is supported by none
584 -- of the type parser components
585 -- of the type stack.
586 | Error_Type_Unsupported_here ast
587 -- ^ Given syntax not supported by the current type parser component.
588 | Error_Type_Wrong_number_of_arguments ast Int
589 deriving (Eq, Show)
590
591 -- | Convenient wrapper around 'lift_error_type',
592 -- passing the type family boilerplate.
593 error_type
594 :: Lift_Error_Type (Error_Type ast)
595 (Error_of_Type ast (Root_of_Type ty))
596 => Proxy ty
597 -> Error_Type ast
598 -> Error_of_Type ast (Root_of_Type ty)
599 error_type _ = lift_error_type
600
601 error_type_unsupported
602 :: forall ast ty.
603 ( Implicit_HBool (Is_Last_Type ty (Root_of_Type ty))
604 , Lift_Error_Type (Error_Type ast) (Error_of_Type ast (Root_of_Type ty))
605 ) => Proxy ty -> ast
606 -> Error_of_Type ast (Root_of_Type ty)
607 error_type_unsupported ty ast =
608 case hbool :: HBool (Is_Last_Type ty (Root_of_Type ty)) of
609 HTrue -> error_type ty $ Error_Type_Unsupported ast
610 HFalse -> error_type ty $ Error_Type_Unsupported_here ast
611
612 -- * Class 'String_from_Type'
613 -- | Return a 'String' from a type.
614 class String_from_Type ty where
615 string_from_type :: ty h -> String
616
617 -- * Type 'Exists_Type'
618 -- | Existential data type wrapping the index of a type.
619 data Exists_Type ty
620 = forall h. Exists_Type (ty h)
621 instance -- Eq
622 Eq_Type ty =>
623 Eq (Exists_Type ty) where
624 Exists_Type xh == Exists_Type yh =
625 isJust $ xh `eq_type` yh
626 instance -- Show
627 String_from_Type ty =>
628 Show (Exists_Type ty) where
629 show (Exists_Type ty) = string_from_type ty
630
631 -- * Type 'Exists_Type1'
632 -- | Existential data type wrapping the index of a type1.
633 data Exists_Type1 ty
634 = forall h. Exists_Type1 (ty h -> ty h)
635
636 -- * Type 'Exists_Type_and_Repr'
637 data Exists_Type_and_Repr ty repr
638 = forall h.
639 Exists_Type_and_Repr (ty h) (repr h)
640
641 -- * Type family 'HBool'
642 -- | Host-type equality.
643 type family HEq x y :: Bool where
644 HEq x x = 'True
645 HEq x y = 'False
646 -- ** Type 'HBool'
647 -- | Boolean singleton.
648 data HBool b where
649 HTrue :: HBool 'True
650 HFalse :: HBool 'False
651 -- ** Class 'Implicit_HBool'
652 -- | Construct a host-term boolean singleton from a host-type boolean.
653 class Implicit_HBool b where hbool :: HBool b
654 instance Implicit_HBool 'True where hbool = HTrue
655 instance Implicit_HBool 'False where hbool = HFalse