]> Git — Sourcephile - haskell/symantic.git/blob - Language/Symantic/Type/Tuple.hs
Map
[haskell/symantic.git] / Language / Symantic / Type / Tuple.hs
1 {-# LANGUAGE FlexibleContexts #-}
2 {-# LANGUAGE FlexibleInstances #-}
3 {-# LANGUAGE MultiParamTypeClasses #-}
4 {-# LANGUAGE PatternSynonyms #-}
5 {-# LANGUAGE ScopedTypeVariables #-}
6 {-# LANGUAGE TypeFamilies #-}
7 {-# OPTIONS_GHC -fno-warn-orphans #-}
8 module Language.Symantic.Type.Tuple where
9
10 import Data.Proxy
11 import Data.Type.Equality ((:~:)(Refl))
12 import Language.Symantic.Type.Root
13 import Language.Symantic.Type.Type0
14 import Language.Symantic.Type.Type1
15 import Language.Symantic.Type.Type2
16
17 -- * Type 'Type_Tuple2'
18 -- | The @(,)@ type.
19 type Type_Tuple2 = Type_Type2 (Proxy (,))
20
21 pattern Type_Tuple2
22 :: root a -> root b
23 -> Type_Tuple2 root ((,) a b)
24 pattern Type_Tuple2 a b
25 = Type_Type2 Proxy a b
26
27 instance Unlift_Type1 Type_Tuple2 where
28 unlift_type1 (Type_Type2 px a b) k =
29 k ( Type_Type1 (Proxy::Proxy ((,) a)) b
30 , Lift_Type1 (\(Type_Type1 _ b') -> Type_Type2 px a b')
31 )
32 instance
33 Constraint_Type Eq root =>
34 Constraint_Type Eq (Type_Tuple2 root) where
35 constraint_type c (Type_Type2 _ a b)
36 | Just Dict <- constraint_type c a
37 , Just Dict <- constraint_type c b
38 = Just Dict
39 constraint_type _c _ = Nothing
40 instance
41 Constraint_Type Ord root =>
42 Constraint_Type Ord (Type_Tuple2 root) where
43 constraint_type c (Type_Type2 _ a b)
44 | Just Dict <- constraint_type c a
45 , Just Dict <- constraint_type c b
46 = Just Dict
47 constraint_type _c _ = Nothing
48 instance Constraint_Type1 Functor (Type_Tuple2 root) where
49 constraint_type1 _c Type_Type2{} = Just Dict
50 instance
51 Constraint_Type Monoid root =>
52 Constraint_Type1 Applicative (Type_Tuple2 root) where
53 constraint_type1 _c (Type_Type2 _ a _b)
54 | Just Dict <- constraint_type (Proxy::Proxy Monoid) a
55 = Just Dict
56 constraint_type1 _c _ = Nothing
57 instance Constraint_Type1 Foldable (Type_Tuple2 root) where
58 constraint_type1 _c Type_Type2{} = Just Dict
59 instance Constraint_Type1 Traversable (Type_Tuple2 root) where
60 constraint_type1 _c Type_Type2{} = Just Dict
61 instance
62 Constraint_Type Monoid root =>
63 Constraint_Type Monoid (Type_Tuple2 root) where
64 constraint_type c (Type_Type2 _ a b)
65 | Just Dict <- constraint_type c a
66 , Just Dict <- constraint_type c b
67 = Just Dict
68 constraint_type _c _ = Nothing
69 instance -- Eq_Type
70 Eq_Type root =>
71 Eq_Type (Type_Tuple2 root) where
72 eq_type (Type_Type2 _px1 a1 b1) (Type_Type2 _px2 a2 b2)
73 | Just Refl <- a1 `eq_type` a2
74 , Just Refl <- b1 `eq_type` b2
75 = Just Refl
76 eq_type _ _ = Nothing
77 instance -- Eq_Type1
78 Eq_Type root =>
79 Eq_Type1 (Type_Tuple2 root) where
80 eq_type1 (Type_Type2 _px1 a1 _b1) (Type_Type2 _px2 a2 _b2)
81 | Just Refl <- a1 `eq_type` a2
82 = Just Refl
83 eq_type1 _ _ = Nothing
84 instance -- String_from_Type
85 String_from_Type root =>
86 String_from_Type (Type_Tuple2 root) where
87 string_from_type (Type_Type2 _ a b) =
88 "(" ++ string_from_type a ++
89 ", " ++ string_from_type b ++ ")"
90
91 -- | Inject 'Type_Tuple2' within a root type.
92 type_tuple2
93 :: forall root h_a h_b.
94 Lift_Type_Root Type_Tuple2 root
95 => root h_a
96 -> root h_b
97 -> root (h_a, h_b)
98 type_tuple2 a b = lift_type_root
99 (Type_Tuple2 a b
100 ::Type_Tuple2 root (h_a, h_b))