]> Git — Sourcephile - haskell/symantic.git/blob - Language/LOL/Symantic/Type/Maybe.hs
init
[haskell/symantic.git] / Language / LOL / Symantic / Type / Maybe.hs
1 {-# LANGUAGE FlexibleContexts #-}
2 {-# LANGUAGE GADTs #-}
3 {-# LANGUAGE MultiParamTypeClasses #-}
4 {-# LANGUAGE OverloadedStrings #-}
5 {-# LANGUAGE ScopedTypeVariables #-}
6 {-# LANGUAGE TypeFamilies #-}
7 {-# LANGUAGE UndecidableInstances #-}
8 module Language.LOL.Symantic.Type.Maybe where
9
10 import Data.Maybe (isJust)
11 import Data.Type.Equality ((:~:)(Refl))
12
13 import Language.LOL.Symantic.Type.Common
14 import Language.LOL.Symantic.Type.Fun
15 import Language.LOL.Symantic.Type.Bool
16 import Language.LOL.Symantic.Type.Var
17
18 -- * Type 'Type_Maybe'
19 -- | The 'Maybe' type.
20 data Type_Maybe root h where
21 Type_Maybe :: root h_a
22 -> Type_Maybe root (Maybe h_a)
23
24 type instance Root_of_Type (Type_Maybe root) = root
25 type instance Error_of_Type ast (Type_Maybe root) = ()
26
27 instance -- Type_Eq
28 Type_Eq root =>
29 Type_Eq (Type_Maybe root) where
30 type_eq (Type_Maybe a1) (Type_Maybe a2)
31 | Just Refl <- a1 `type_eq` a2
32 = Just Refl
33 type_eq _ _ = Nothing
34 instance -- Eq
35 Type_Eq root =>
36 Eq (Type_Maybe root h) where
37 x == y = isJust $ type_eq x y
38 instance -- String_from_Type
39 String_from_Type root =>
40 String_from_Type (Type_Maybe root) where
41 string_from_type (Type_Maybe a) =
42 "Maybe (" ++ string_from_type a ++ ")"
43 instance -- Show
44 String_from_Type root =>
45 Show (Type_Maybe root h) where
46 show = string_from_type
47
48 -- | Convenient alias to include a 'Type_Maybe' within a type.
49 type_maybe
50 :: Type_Root_Lift Type_Maybe root
51 => root h_a
52 -> root (Maybe h_a)
53 type_maybe a = type_root_lift (Type_Maybe a)
54
55 -- * Type 'Type_Fun_Bool_Maybe'
56 -- | Convenient alias.
57 type Type_Fun_Bool_Maybe lam
58 = Type_Root (Type_Alt Type_Var
59 (Type_Alt (Type_Fun lam)
60 (Type_Alt Type_Bool
61 Type_Maybe)))