1 {-# LANGUAGE FlexibleContexts #-}
2 {-# LANGUAGE FlexibleInstances #-}
3 {-# LANGUAGE PatternSynonyms #-}
4 {-# LANGUAGE TypeFamilies #-}
5 {-# OPTIONS_GHC -fno-warn-orphans #-}
6 module Language.Symantic.Type.Maybe where
9 import Data.Type.Equality ((:~:)(Refl))
10 import Language.Symantic.Type.Common
12 -- * Type 'Type_Maybe'
13 -- | The 'Maybe' type.
14 type Type_Maybe = Type_Type1 (Proxy Maybe)
16 pattern Type_Map :: root a -> Type_Maybe root (Maybe a)
17 pattern Type_Map a = Type_Type1 Proxy a
21 Eq_Type (Type_Type1 (Proxy Maybe) root) where
22 eq_type (Type_Type1 _px1 a1) (Type_Type1 _px2 a2)
23 | Just Refl <- a1 `eq_type` a2
27 Eq_Type1 (Type_Type1 (Proxy Maybe) root) where
28 eq_type1 Type_Type1{} Type_Type1{}
30 instance -- String_from_Type
31 String_from_Type root =>
32 String_from_Type (Type_Maybe root) where
33 string_from_type (Type_Type1 _f a) =
34 "Maybe" ++ " (" ++ string_from_type a ++ ")"
36 -- | Inject 'Type_Maybe' within a root type.
38 :: Lift_Type_Root Type_Maybe root
41 type_maybe = lift_type_root . Type_Type1 (Proxy::Proxy Maybe)