{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# OPTIONS_GHC -fno-warn-orphans #-} module Language.Symantic.Type.Either where import Data.Proxy import Data.Type.Equality ((:~:)(Refl)) import qualified Data.MonoTraversable as MT import Language.Symantic.Type.Root import Language.Symantic.Type.Type0 import Language.Symantic.Type.Type1 import Language.Symantic.Type.Type2 import Language.Symantic.Type.Constraint import Language.Symantic.Type.Family -- * Type 'Type_Either' -- | The 'Either' type. type Type_Either = Type2 (Proxy Either) pattern Type_Either :: root l -> root r -> Type_Either root (Either l r) pattern Type_Either l r = Type2 Proxy l r instance Type1_Unlift Type_Either where type1_unlift (Type2 px a b) k = k ( Type1 (Proxy::Proxy (Either a)) b , Type1_Lift (\(Type1 _ b') -> Type2 px a b') ) instance Type0_Eq root => Type1_Eq (Type_Either root) where type1_eq (Type2 _ a1 _b1) (Type2 _ a2 _b2) | Just Refl <- type0_eq a1 a2 = Just Refl type1_eq _ _ = Nothing instance Type0_Constraint Eq root => Type0_Constraint Eq (Type_Either root) where type0_constraint c (Type2 _ l r) | Just Dict <- type0_constraint c l , Just Dict <- type0_constraint c r = Just Dict type0_constraint _c _ = Nothing instance Type0_Constraint Ord root => Type0_Constraint Ord (Type_Either root) where type0_constraint c (Type2 _ l r) | Just Dict <- type0_constraint c l , Just Dict <- type0_constraint c r = Just Dict type0_constraint _c _ = Nothing instance Type0_Constraint Num (Type_Either root) instance Type0_Constraint Integral (Type_Either root) instance Type0_Constraint MT.MonoFunctor (Type_Either root) where type0_constraint _c Type2{} = Just Dict instance Type1_Constraint Functor (Type_Either root) where type1_constraint _c Type2{} = Just Dict instance Type1_Constraint Applicative (Type_Either root) where type1_constraint _c Type2{} = Just Dict instance Type1_Constraint Traversable (Type_Either root) where type1_constraint _c Type2{} = Just Dict instance Type1_Constraint Foldable (Type_Either root) where type1_constraint _c Type2{} = Just Dict instance Type1_Constraint Monad (Type_Either root) where type1_constraint _c Type2{} = Just Dict instance Type0_Family Type_Family_MonoElement (Type_Either root) where type0_family _at (Type2 _px _l r) = Just r instance -- Type0_Eq Type0_Eq root => Type0_Eq (Type_Either root) where type0_eq (Type2 _ l1 r1) (Type2 _ l2 r2) | Just Refl <- l1 `type0_eq` l2 , Just Refl <- r1 `type0_eq` r2 = Just Refl type0_eq _ _ = Nothing instance -- String_from_Type String_from_Type root => String_from_Type (Type_Either root) where string_from_type (Type2 _ l r) = "Either" ++ " (" ++ string_from_type l ++ ")" ++ " (" ++ string_from_type r ++ ")" -- | Inject 'Type_Either' within a root type. type_either :: Type_Root_Lift Type_Either root => root h_l -> root h_r -> root (Either h_l h_r) type_either = type2