]> Git — Sourcephile - haskell/symantic.git/blob - Language/Symantic/Type/Maybe.hs
Monad
[haskell/symantic.git] / Language / Symantic / Type / Maybe.hs
1 {-# LANGUAGE FlexibleContexts #-}
2 {-# LANGUAGE FlexibleInstances #-}
3 {-# LANGUAGE MultiParamTypeClasses #-}
4 {-# LANGUAGE PatternSynonyms #-}
5 {-# LANGUAGE TypeFamilies #-}
6 {-# OPTIONS_GHC -fno-warn-orphans #-}
7 module Language.Symantic.Type.Maybe where
8
9 import Data.Proxy
10 import Data.Type.Equality ((:~:)(Refl))
11 import Language.Symantic.Type.Root
12 import Language.Symantic.Type.Type0
13 import Language.Symantic.Type.Type1
14
15 -- * Type 'Type_Maybe'
16 -- | The 'Maybe' type.
17 type Type_Maybe = Type_Type1 (Proxy Maybe)
18
19 pattern Type_Map :: root a -> Type_Maybe root (Maybe a)
20 pattern Type_Map a = Type_Type1 Proxy a
21
22 instance Constraint_Type1 Monad (Type_Maybe root) where
23 constraint_type1 _c Type_Type1{} = Just Dict
24 instance -- Eq_Type
25 Eq_Type root =>
26 Eq_Type (Type_Maybe root) where
27 eq_type (Type_Type1 _px1 a1) (Type_Type1 _px2 a2)
28 | Just Refl <- a1 `eq_type` a2
29 = Just Refl
30 eq_type _ _ = Nothing
31 instance -- Eq_Type1
32 Eq_Type1 (Type_Maybe root) where
33 eq_type1 Type_Type1{} Type_Type1{}
34 = Just Refl
35 instance -- String_from_Type
36 String_from_Type root =>
37 String_from_Type (Type_Maybe root) where
38 string_from_type (Type_Type1 _f a) =
39 "Maybe" ++ " (" ++ string_from_type a ++ ")"
40
41 -- | Inject 'Type_Maybe' within a root type.
42 type_maybe
43 :: Lift_Type_Root Type_Maybe root
44 => root h_a
45 -> root (Maybe h_a)
46 type_maybe = lift_type_root . Type_Type1 (Proxy::Proxy Maybe)