{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE TypeFamilies #-} {-# OPTIONS_GHC -fno-warn-orphans #-} module Language.Symantic.Type.Maybe where import Data.Proxy import Data.Type.Equality ((:~:)(Refl)) import Language.Symantic.Type.Root import Language.Symantic.Type.Type0 import Language.Symantic.Type.Type1 -- * Type 'Type_Maybe' -- | The 'Maybe' type. type Type_Maybe = Type_Type1 (Proxy Maybe) pattern Type_Map :: root a -> Type_Maybe root (Maybe a) pattern Type_Map a = Type_Type1 Proxy a instance Constraint_Type Eq root => Constraint_Type Eq (Type_Maybe root) where constraint_type c (Type_Type1 _ a) | Just Dict <- constraint_type c a = Just Dict constraint_type _c _ = Nothing instance Constraint_Type Ord root => Constraint_Type Ord (Type_Maybe root) where constraint_type c (Type_Type1 _ a) | Just Dict <- constraint_type c a = Just Dict constraint_type _c _ = Nothing instance Constraint_Type Monoid root => Constraint_Type Monoid (Type_Maybe root) where constraint_type c (Type_Type1 _ a) | Just Dict <- constraint_type c a = Just Dict constraint_type _c _ = Nothing instance Constraint_Type1 Functor (Type_Maybe root) where constraint_type1 _c (Type_Type1 _ _) = Just Dict instance Constraint_Type1 Applicative (Type_Maybe root) where constraint_type1 _c (Type_Type1 _ _) = Just Dict instance Constraint_Type1 Foldable (Type_Maybe root) where constraint_type1 _c (Type_Type1 _ _) = Just Dict instance Constraint_Type1 Traversable (Type_Maybe root) where constraint_type1 _c (Type_Type1 _ _) = Just Dict instance Constraint_Type1 Monad (Type_Maybe root) where constraint_type1 _c Type_Type1{} = Just Dict instance -- Eq_Type Eq_Type root => Eq_Type (Type_Maybe root) where eq_type (Type_Type1 _px1 a1) (Type_Type1 _px2 a2) | Just Refl <- a1 `eq_type` a2 = Just Refl eq_type _ _ = Nothing instance -- Eq_Type1 Eq_Type1 (Type_Maybe root) where eq_type1 Type_Type1{} Type_Type1{} = Just Refl instance -- String_from_Type String_from_Type root => String_from_Type (Type_Maybe root) where string_from_type (Type_Type1 _f a) = "Maybe" ++ " (" ++ string_from_type a ++ ")" -- | Inject 'Type_Maybe' within a root type. type_maybe :: Lift_Type_Root Type_Maybe root => root h_a -> root (Maybe h_a) type_maybe = lift_type_root . Type_Type1 (Proxy::Proxy Maybe)