1{-# LANGUAGE DeriveGeneric #-} 2{-# LANGUAGE TypeOperators #-} 3{-# LANGUAGE GADTs #-} 4{-# LANGUAGE FlexibleInstances #-} 5{-# LANGUAGE StandaloneDeriving #-} 6{-# LANGUAGE NoImplicitPrelude #-} 7{-# LANGUAGE RankNTypes #-} 8{-# LANGUAGE TypeFamilies #-} 9{-# LANGUAGE UndecidableInstances #-} 10{-# LANGUAGE ExplicitNamespaces #-} 11{-# LANGUAGE MultiParamTypeClasses #-} 12{-# LANGUAGE FunctionalDependencies #-} 13{-# LANGUAGE DataKinds #-} 14{-# LANGUAGE PolyKinds #-} 15{-# LANGUAGE StandaloneKindSignatures #-} 16{-# LANGUAGE Trustworthy #-} 17 18----------------------------------------------------------------------------- 19-- | 20-- Module : Data.Type.Equality 21-- License : BSD-style (see the LICENSE file in the distribution) 22-- 23-- Maintainer : libraries@haskell.org 24-- Stability : experimental 25-- Portability : not portable 26-- 27-- Definition of propositional equality @(':~:')@. Pattern-matching on a variable 28-- of type @(a ':~:' b)@ produces a proof that @a '~' b@. 29-- 30-- @since 4.7.0.0 31----------------------------------------------------------------------------- 32 33 34 35module Data.Type.Equality ( 36 -- * The equality types 37 (:~:)(..), type (~~), 38 (:~~:)(..), 39 40 -- * Working with equality 41 sym, trans, castWith, gcastWith, apply, inner, outer, 42 43 -- * Inferring equality from other types 44 TestEquality(..), 45 46 -- * Boolean type-level equality 47 type (==) 48 ) where 49 50import Data.Maybe 51import GHC.Enum 52import GHC.Show 53import GHC.Read 54import GHC.Base 55import Data.Type.Bool 56 57infix 4 :~:, :~~: 58 59-- | Propositional equality. If @a :~: b@ is inhabited by some terminating 60-- value, then the type @a@ is the same as the type @b@. To use this equality 61-- in practice, pattern-match on the @a :~: b@ to get out the @Refl@ constructor; 62-- in the body of the pattern-match, the compiler knows that @a ~ b@. 63-- 64-- @since 4.7.0.0 65data a :~: b where -- See Note [The equality types story] in TysPrim 66 Refl :: a :~: a 67 68-- with credit to Conal Elliott for 'ty', Erik Hesselink & Martijn van 69-- Steenbergen for 'type-equality', Edward Kmett for 'eq', and Gabor Greif 70-- for 'type-eq' 71 72-- | Symmetry of equality 73sym :: (a :~: b) -> (b :~: a) 74sym Refl = Refl 75 76-- | Transitivity of equality 77trans :: (a :~: b) -> (b :~: c) -> (a :~: c) 78trans Refl Refl = Refl 79 80-- | Type-safe cast, using propositional equality 81castWith :: (a :~: b) -> a -> b 82castWith Refl x = x 83 84-- | Generalized form of type-safe cast using propositional equality 85gcastWith :: (a :~: b) -> ((a ~ b) => r) -> r 86gcastWith Refl x = x 87 88-- | Apply one equality to another, respectively 89apply :: (f :~: g) -> (a :~: b) -> (f a :~: g b) 90apply Refl Refl = Refl 91 92-- | Extract equality of the arguments from an equality of applied types 93inner :: (f a :~: g b) -> (a :~: b) 94inner Refl = Refl 95 96-- | Extract equality of type constructors from an equality of applied types 97outer :: (f a :~: g b) -> (f :~: g) 98outer Refl = Refl 99 100-- | @since 4.7.0.0 101deriving instance Eq (a :~: b) 102 103-- | @since 4.7.0.0 104deriving instance Show (a :~: b) 105 106-- | @since 4.7.0.0 107deriving instance Ord (a :~: b) 108 109-- | @since 4.7.0.0 110deriving instance a ~ b => Read (a :~: b) 111 112-- | @since 4.7.0.0 113instance a ~ b => Enum (a :~: b) where 114 toEnum 0 = Refl 115 toEnum _ = errorWithoutStackTrace "Data.Type.Equality.toEnum: bad argument" 116 117 fromEnum Refl = 0 118 119-- | @since 4.7.0.0 120deriving instance a ~ b => Bounded (a :~: b) 121 122-- | Kind heterogeneous propositional equality. Like ':~:', @a :~~: b@ is 123-- inhabited by a terminating value if and only if @a@ is the same type as @b@. 124-- 125-- @since 4.10.0.0 126type (:~~:) :: k1 -> k2 -> Type 127data a :~~: b where 128 HRefl :: a :~~: a 129 130-- | @since 4.10.0.0 131deriving instance Eq (a :~~: b) 132-- | @since 4.10.0.0 133deriving instance Show (a :~~: b) 134-- | @since 4.10.0.0 135deriving instance Ord (a :~~: b) 136 137-- | @since 4.10.0.0 138deriving instance a ~~ b => Read (a :~~: b) 139 140-- | @since 4.10.0.0 141instance a ~~ b => Enum (a :~~: b) where 142 toEnum 0 = HRefl 143 toEnum _ = errorWithoutStackTrace "Data.Type.Equality.toEnum: bad argument" 144 145 fromEnum HRefl = 0 146 147-- | @since 4.10.0.0 148deriving instance a ~~ b => Bounded (a :~~: b) 149 150-- | This class contains types where you can learn the equality of two types 151-- from information contained in /terms/. Typically, only singleton types should 152-- inhabit this class. 153class TestEquality f where 154 -- | Conditionally prove the equality of @a@ and @b@. 155 testEquality :: f a -> f b -> Maybe (a :~: b) 156 157-- | @since 4.7.0.0 158instance TestEquality ((:~:) a) where 159 testEquality Refl Refl = Just Refl 160 161-- | @since 4.10.0.0 162instance TestEquality ((:~~:) a) where 163 testEquality HRefl HRefl = Just Refl 164 165infix 4 == 166 167-- | A type family to compute Boolean equality. 168type (==) :: k -> k -> Bool 169type family a == b where 170 f a == g b = f == g && a == b 171 a == a = 'True 172 _ == _ = 'False 173 174-- The idea here is to recognize equality of *applications* using 175-- the first case, and of *constructors* using the second and third 176-- ones. It would be wonderful if GHC recognized that the 177-- first and second cases are compatible, which would allow us to 178-- prove 179-- 180-- a ~ b => a == b 181-- 182-- but it (understandably) does not. 183-- 184-- It is absolutely critical that the three cases occur in precisely 185-- this order. In particular, if 186-- 187-- a == a = 'True 188-- 189-- came first, then the type application case would only be reached 190-- (uselessly) when GHC discovered that the types were not equal. 191-- 192-- One might reasonably ask what's wrong with a simpler version: 193-- 194-- type family (a :: k) == (b :: k) where 195-- a == a = True 196-- a == b = False 197-- 198-- Consider 199-- data Nat = Zero | Succ Nat 200-- 201-- Suppose I want 202-- foo :: (Succ n == Succ m) ~ True => ((n == m) :~: True) 203-- foo = Refl 204-- 205-- This would not type-check with the simple version. `Succ n == Succ m` 206-- is stuck. We don't know enough about `n` and `m` to reduce the family. 207-- With the recursive version, `Succ n == Succ m` reduces to 208-- `Succ == Succ && n == m`, which can reduce to `'True && n == m` and 209-- finally to `n == m`. 210