{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# OPTIONS_GHC -fno-warn-orphans #-} module Language.Symantic.Type.Tuple where 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 -- * Type 'Type_Tuple2' -- | The @(,)@ type. type Type_Tuple2 = Type_Type2 (Proxy (,)) pattern Type_Tuple2 :: root a -> root b -> Type_Tuple2 root ((,) a b) pattern Type_Tuple2 a b = Type_Type2 Proxy a b instance Unlift_Type1 Type_Tuple2 where unlift_type1 (Type_Type2 px a b) k = k ( Type_Type1 (Proxy::Proxy ((,) a)) b , Lift_Type1 (\(Type_Type1 _ b') -> Type_Type2 px a b') ) instance Constraint_Type Eq root => Constraint_Type Eq (Type_Tuple2 root) where constraint_type c (Type_Type2 _ a b) | Just Dict <- constraint_type c a , Just Dict <- constraint_type c b = Just Dict constraint_type _c _ = Nothing instance Constraint_Type Ord root => Constraint_Type Ord (Type_Tuple2 root) where constraint_type c (Type_Type2 _ a b) | Just Dict <- constraint_type c a , Just Dict <- constraint_type c b = Just Dict constraint_type _c _ = Nothing instance Constraint_Type Monoid root => Constraint_Type Monoid (Type_Tuple2 root) where constraint_type c (Type_Type2 _ a b) | Just Dict <- constraint_type c a , Just Dict <- constraint_type c b = Just Dict constraint_type _c _ = Nothing instance Constraint_Type Num (Type_Tuple2 root) instance Constraint_Type Integral (Type_Tuple2 root) instance Constraint_Type1 Functor (Type_Tuple2 root) where constraint_type1 _c Type_Type2{} = Just Dict instance Constraint_Type Monoid root => Constraint_Type1 Applicative (Type_Tuple2 root) where constraint_type1 _c (Type_Type2 _ a _b) | Just Dict <- constraint_type (Proxy::Proxy Monoid) a = Just Dict constraint_type1 _c _ = Nothing instance Constraint_Type1 Foldable (Type_Tuple2 root) where constraint_type1 _c Type_Type2{} = Just Dict instance Constraint_Type1 Traversable (Type_Tuple2 root) where constraint_type1 _c Type_Type2{} = Just Dict instance -- Eq_Type Eq_Type root => Eq_Type (Type_Tuple2 root) where eq_type (Type_Type2 _px1 a1 b1) (Type_Type2 _px2 a2 b2) | Just Refl <- a1 `eq_type` a2 , Just Refl <- b1 `eq_type` b2 = Just Refl eq_type _ _ = Nothing instance -- Eq_Type1 Eq_Type root => Eq_Type1 (Type_Tuple2 root) where eq_type1 (Type_Type2 _px1 a1 _b1) (Type_Type2 _px2 a2 _b2) | Just Refl <- a1 `eq_type` a2 = Just Refl eq_type1 _ _ = Nothing instance -- String_from_Type String_from_Type root => String_from_Type (Type_Tuple2 root) where string_from_type (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. Lift_Type_Root Type_Tuple2 root => root h_a -> root h_b -> root (h_a, h_b) type_tuple2 a b = lift_type_root (Type_Tuple2 a b ::Type_Tuple2 root (h_a, h_b))