{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE TypeFamilies #-} {-# OPTIONS_GHC -fno-warn-orphans #-} module Language.Symantic.Type.Maybe where import qualified Data.MonoTraversable as MT import Data.Proxy import Data.Type.Equality ((:~:)(Refl)) import Language.Symantic.Type.Root import Language.Symantic.Type.Type0 import Language.Symantic.Type.Type1 import Language.Symantic.Type.Constraint import Language.Symantic.Type.Family -- * Type 'Type_Maybe' -- | The 'Maybe' type. type Type_Maybe = Type1 (Proxy Maybe) pattern Type_Maybe :: root a -> Type_Maybe root (Maybe a) pattern Type_Maybe a = Type1 Proxy a instance Type0_Constraint Eq root => Type0_Constraint Eq (Type_Maybe root) where type0_constraint c (Type1 _ a) | Just Dict <- type0_constraint c a = Just Dict type0_constraint _c _ = Nothing instance Type0_Constraint Ord root => Type0_Constraint Ord (Type_Maybe root) where type0_constraint c (Type1 _ a) | Just Dict <- type0_constraint c a = Just Dict type0_constraint _c _ = Nothing instance Type0_Constraint Monoid root => Type0_Constraint Monoid (Type_Maybe root) where type0_constraint c (Type1 _ a) | Just Dict <- type0_constraint c a = Just Dict type0_constraint _c _ = Nothing instance Type0_Constraint Num (Type_Maybe root) instance Type0_Constraint Integral (Type_Maybe root) instance Type0_Constraint MT.MonoFunctor (Type_Maybe root) where type0_constraint _c Type1{} = Just Dict instance Type1_Constraint Functor (Type_Maybe root) where type1_constraint _c (Type1 _ _) = Just Dict instance Type1_Constraint Applicative (Type_Maybe root) where type1_constraint _c (Type1 _ _) = Just Dict instance Type1_Constraint Foldable (Type_Maybe root) where type1_constraint _c (Type1 _ _) = Just Dict instance Type1_Constraint Traversable (Type_Maybe root) where type1_constraint _c (Type1 _ _) = Just Dict instance Type1_Constraint Monad (Type_Maybe root) where type1_constraint _c Type1{} = Just Dict instance Type0_Family Type_Family_MonoElement (Type_Maybe root) where type0_family _at (Type1 _px a) = Just a instance -- Type0_Eq Type0_Eq root => Type0_Eq (Type_Maybe root) where type0_eq (Type1 _px1 a1) (Type1 _px2 a2) | Just Refl <- a1 `type0_eq` a2 = Just Refl type0_eq _ _ = Nothing instance -- Type1_Eq Type1_Eq (Type_Maybe root) where type1_eq Type1{} Type1{} = Just Refl instance -- String_from_Type String_from_Type root => String_from_Type (Type_Maybe root) where string_from_type (Type1 _f a) = "Maybe" ++ " (" ++ string_from_type a ++ ")" -- | Inject 'Type_Maybe' within a root type. type_maybe :: Type_Root_Lift Type_Maybe root => root h_a -> root (Maybe h_a) type_maybe = type1