{-# 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 -- * Type 'Type_Either' -- | The 'Either' type. type Type_Either = Type_Type2 (Proxy Either) instance Unlift_Type1 Type_Either where unlift_type1 (Type_Type2 px a b) k = k ( Type_Type1 (Proxy::Proxy (Either a)) b , Lift_Type1 (\(Type_Type1 _ b') -> Type_Type2 px a b') ) instance Eq_Type root => Eq_Type1 (Type_Either root) where eq_type1 (Type_Type2 _ a1 _b1) (Type_Type2 _ a2 _b2) | Just Refl <- eq_type a1 a2 = Just Refl eq_type1 _ _ = Nothing instance Constraint_Type Eq root => Constraint_Type Eq (Type_Either root) where constraint_type c (Type_Type2 _ l r) | Just Dict <- constraint_type c l , Just Dict <- constraint_type c r = Just Dict constraint_type _c _ = Nothing instance Constraint_Type Ord root => Constraint_Type Ord (Type_Either root) where constraint_type c (Type_Type2 _ l r) | Just Dict <- constraint_type c l , Just Dict <- constraint_type c r = Just Dict constraint_type _c _ = Nothing instance Constraint_Type Num (Type_Either root) instance Constraint_Type Integral (Type_Either root) instance Constraint_Type MT.MonoFunctor (Type_Either root) where constraint_type _c Type_Type2{} = Just Dict instance Constraint_Type1 Functor (Type_Either root) where constraint_type1 _c Type_Type2{} = Just Dict instance Constraint_Type1 Applicative (Type_Either root) where constraint_type1 _c Type_Type2{} = Just Dict instance Constraint_Type1 Traversable (Type_Either root) where constraint_type1 _c Type_Type2{} = Just Dict instance Constraint_Type1 Monad (Type_Either root) where constraint_type1 _c Type_Type2{} = Just Dict pattern Type_Either :: root l -> root r -> Type_Either root (Either l r) pattern Type_Either l r = Type_Type2 Proxy l r instance -- Eq_Type Eq_Type root => Eq_Type (Type_Either root) where eq_type (Type_Type2 _ l1 r1) (Type_Type2 _ l2 r2) | Just Refl <- l1 `eq_type` l2 , Just Refl <- r1 `eq_type` r2 = Just Refl eq_type _ _ = Nothing instance -- String_from_Type String_from_Type root => String_from_Type (Type_Either root) where string_from_type (Type_Type2 _ l r) = "Either" ++ " (" ++ string_from_type l ++ ")" ++ " (" ++ string_from_type r ++ ")" -- | Inject 'Type_Either' within a root type. type_either :: forall root h_l h_r. Lift_Type_Root Type_Either root => root h_l -> root h_r -> root (Either h_l h_r) type_either = type_type2