File: Equality.hs

package info (click to toggle)
haskell-type-equality 1-2
  • links: PTS
  • area: main
  • in suites: bullseye
  • size: 92 kB
  • sloc: haskell: 177; makefile: 5
file content (212 lines) | stat: -rw-r--r-- 6,215 bytes parent folder | download | duplicates (2)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
{-# LANGUAGE CPP                 #-}
#if __GLASGOW_HASKELL__ >= 708
#error "Trying to compiled Data.Type.Equality module with GHC-7.8+"
#endif
{-# LANGUAGE GADTs               #-}
{-# LANGUAGE RankNTypes          #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving  #-}
{-# LANGUAGE TypeFamilies        #-}
{-# LANGUAGE TypeOperators       #-}
#if __GLASGOW_HASKELL__ >= 706
{-# LANGUAGE PolyKinds           #-}
#endif
#if __GLASGOW_HASKELL__ >= 702
-- only Trustworthy, as we have manual Typeable instance
{-# LANGUAGE Trustworthy         #-}
#endif
module Data.Type.Equality (
    -- * Type equality
    (:~:) (..),
    -- * Combinators
    sym,
    trans,
    castWith,
    gcastWith,

#if __GLASGOW_HASKELL__ >= 706
    apply,
#endif
    inner,
#if __GLASGOW_HASKELL__ >= 706
    outer,
#endif

    -- inner and outer not implemented,
    -- as GHC-7.6 fails to infer them:
    --    Could not deduce (f ~ g) from the context (f a ~ g b)

    -- There are no (==) as it needs ClosedTypeFamilies (since GHC-7.8)

    -- * TestEquality
    --
    -- | Provided only for GHC-7.6.
    -- Also there isn't @==@ type family, as it requires close type families,
    -- which are available only since GHC-7.8.
    TestEquality (..),
    ) where

import qualified Control.Category as C
import Data.Typeable (Typeable2 (..), Typeable)
import Data.Data (Data (..), Constr, mkConstr, Fixity(Prefix), DataType, mkDataType, mkTyConApp, TyCon)

#if MIN_VERSION_base(4,4,0)
import Data.Data (mkTyCon3)
#else
import Data.Data (mkTyCon)
#endif

#ifndef CURRENT_PACKAGE_KEY
import Data.Version (showVersion)
import Paths_type_equality_compat (version)
#endif

-- | Propositional equality. If @a ':~:' b@ is inhabited by some
-- terminating value, then the type @a@ is the same as the type
-- @b@. To use this equality in practice, pattern-match on the
-- @a ':~:' b@ to get out the 'Refl' constructor; in the body of
-- the pattern-match, the compiler knows that @a ~ b@.
--
-- /Note:/ this definition is polykinded only since GHC-7.6.
--
data a :~: b where
    Refl :: a :~: a

deriving instance Eq (a :~: b)
deriving instance Ord (a :~: b)
deriving instance a ~ b => Read (a :~: b)
deriving instance Show (a :~: b)

instance C.Category (:~:) where
    id = Refl
    Refl . Refl = Refl

instance a ~ b => Enum (a :~: b) where
    toEnum 0 = Refl
    toEnum _ = error "Data.Type.Equality.toEnum: bad argument"

    fromEnum Refl = 0

instance a ~ b => Bounded (a :~: b) where
    minBound = Refl
    maxBound = Refl

-------------------------------------------------------------------------------
-- Typeable & Data
-------------------------------------------------------------------------------

instance Typeable2 (:~:) where
    typeOf2 _ = mkTyConApp eqTyCon []

typeEqualityCompatPackageKey :: String
#ifdef CURRENT_PACKAGE_KEY
typeEqualityCompatPackageKey = CURRENT_PACKAGE_KEY
#else
typeEqualityCompatPackageKey = "type-equality-compat-" ++ showVersion version
#endif

eqTyCon :: TyCon
#if MIN_VERSION_base(4,4,0)
eqTyCon = mkTyCon3 typeEqualityCompatPackageKey "Data.Type.Equality" ":~:"
#else
eqTyCon = mkTyCon "Data.Type.Equality.:~:"
#endif

instance (Typeable a, Typeable b, a ~ b) => Data (a :~: b) where
    gfoldl _ z Refl = z Refl
    gunfold _ z _ = z Refl
    toConstr Refl = reflConstr
    dataTypeOf _ = eqDataType

eqDataType :: DataType
eqDataType = mkDataType ":~:" [reflConstr]

reflConstr :: Constr
reflConstr = mkConstr eqDataType "Refl" [] Prefix

-------------------------------------------------------------------------------
-- Combinators
-------------------------------------------------------------------------------

-- | Symmetry of equality
sym :: (a :~: b) -> (b :~: a)
sym Refl = Refl

-- | Transitivity of equality
trans :: (a :~: b) -> (b :~: c) -> (a :~: c)
trans Refl Refl = Refl

-- | Type-safe cast, using propositional equality
castWith :: (a :~: b) -> a -> b
castWith Refl x = x

-- | Generalized form of type-safe cast using propositional equality
gcastWith :: (a :~: b) -> ((a ~ b) => r) -> r
gcastWith Refl x = x

#if __GLASGOW_HASKELL__ >= 706
-- | Apply one equality to another, respectively
apply :: (f :~: g) -> (a :~: b) -> (f a :~: g b)
apply Refl Refl = Refl
#endif

-- | Extract equality of the arguments from an equality of applied types
inner :: f a :~: g b -> a :~: b
inner = fromLeibniz . innerLeibniz . toLeibniz

#if __GLASGOW_HASKELL__ >= 706
-- | Extract equality of type constructors from an equality of applied types
outer :: f a :~: g b -> f :~: g
outer = fromLeibniz . outerLeibniz . toLeibniz
#endif

-------------------------------------------------------------------------------
-- TestEquality
-------------------------------------------------------------------------------

-- | This class contains types where you can learn the equality of two types
-- from information contained in /terms/. Typically, only singleton types should
-- inhabit this class.
class TestEquality f where
  -- | Conditionally prove the equality of @a@ and @b@.
  testEquality :: f a -> f b -> Maybe (a :~: b)

instance TestEquality ((:~:) a) where
  testEquality Refl Refl = Just Refl

-------------------------------------------------------------------------------
-- Leibniz
-------------------------------------------------------------------------------

newtype a := b = ReflLeibniz { subst :: forall c. c a -> c b }

reflLeibniz :: a := a
reflLeibniz = ReflLeibniz id

#if __GLASGOW_HASKELL__ >= 706
type family Inj (f :: j -> k) (a :: k) :: j
#else
type family Inj (f :: * -> *) (a :: *) :: *
#endif
type instance Inj f (g a) = a

newtype Lower f a b = Lower { unlower :: Inj f a := Inj f b }

fromLeibniz :: a := b -> a :~: b
fromLeibniz a = subst a Refl

toLeibniz :: a :~: b -> a := b
toLeibniz Refl = reflLeibniz

innerLeibniz :: f a := g b -> a := b
innerLeibniz eq = unlower (subst eq (Lower reflLeibniz :: Lower f (f a) (f a)))

#if __GLASGOW_HASKELL__ >= 706
type family Gen (f :: j -> k) (a :: k) :: j -> k
type instance Gen f (g a) = g

newtype Generate f a b = Generate { ungenerate :: Gen f a := Gen f b }

outerLeibniz :: f a := g b -> f := g
outerLeibniz eq = ungenerate (subst eq (Generate reflLeibniz :: Generate f (f a) (f a)))
#endif