{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# OPTIONS_GHC -fno-warn-orphans #-} module Language.Symantic.Type.Tuple 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.Type2 import Language.Symantic.Type.Constraint import Language.Symantic.Type.Family -- * Type 'Type_Tuple2' -- | The @(,)@ type. type Type_Tuple2 = Type2 (Proxy (,)) pattern Type_Tuple2 :: root a -> root b -> Type_Tuple2 root ((,) a b) pattern Type_Tuple2 a b = Type2 Proxy a b instance Type1_Unlift Type_Tuple2 where type1_unlift (Type2 px a b) k = k ( Type1 (Proxy::Proxy ((,) a)) b , Type1_Lift (\(Type1 _ b') -> Type2 px a b') ) instance Type0_Constraint Eq root => Type0_Constraint Eq (Type_Tuple2 root) where type0_constraint c (Type2 _ a b) | Just Dict <- type0_constraint c a , Just Dict <- type0_constraint c b = Just Dict type0_constraint _c _ = Nothing instance Type0_Constraint Ord root => Type0_Constraint Ord (Type_Tuple2 root) where type0_constraint c (Type2 _ a b) | Just Dict <- type0_constraint c a , Just Dict <- type0_constraint c b = Just Dict type0_constraint _c _ = Nothing instance Type0_Constraint Monoid root => Type0_Constraint Monoid (Type_Tuple2 root) where type0_constraint c (Type2 _ a b) | Just Dict <- type0_constraint c a , Just Dict <- type0_constraint c b = Just Dict type0_constraint _c _ = Nothing instance Type0_Constraint Num (Type_Tuple2 root) instance Type0_Constraint Integral (Type_Tuple2 root) instance Type0_Constraint MT.MonoFunctor (Type_Tuple2 root) where type0_constraint _c Type2{} = Just Dict instance Type1_Constraint Functor (Type_Tuple2 root) where type1_constraint _c Type2{} = Just Dict instance Type0_Constraint Monoid root => Type1_Constraint Applicative (Type_Tuple2 root) where type1_constraint _c (Type2 _ a _b) | Just Dict <- type0_constraint (Proxy::Proxy Monoid) a = Just Dict type1_constraint _c _ = Nothing instance Type1_Constraint Foldable (Type_Tuple2 root) where type1_constraint _c Type2{} = Just Dict instance Type1_Constraint Traversable (Type_Tuple2 root) where type1_constraint _c Type2{} = Just Dict instance Type0_Family Type_Family_MonoElement (Type_Tuple2 root) where type0_family _at (Type2 _px _a b) = Just b instance -- Type0_Eq Type0_Eq root => Type0_Eq (Type_Tuple2 root) where type0_eq (Type2 _px1 a1 b1) (Type2 _px2 a2 b2) | Just Refl <- a1 `type0_eq` a2 , Just Refl <- b1 `type0_eq` b2 = Just Refl type0_eq _ _ = Nothing instance -- Type1_Eq Type0_Eq root => Type1_Eq (Type_Tuple2 root) where type1_eq (Type2 _px1 a1 _b1) (Type2 _px2 a2 _b2) | Just Refl <- a1 `type0_eq` a2 = Just Refl type1_eq _ _ = Nothing instance -- String_from_Type String_from_Type root => String_from_Type (Type_Tuple2 root) where string_from_type (Type2 _ a b) = "(" ++ string_from_type a ++ ", " ++ string_from_type b ++ ")" -- | Inject 'Type_Tuple2' within a root type. type_tuple2 :: forall root h_a h_b. Type_Root_Lift Type_Tuple2 root => root h_a -> root h_b -> root (h_a, h_b) type_tuple2 = type2