[commit: packages/base] master: Name change `CoercionT` to `CoercionType`, and addition of `repr`. (fd86260)

git at git.haskell.org git at git.haskell.org
Mon Oct 28 19:20:03 UTC 2013


Repository : ssh://git@git.haskell.org/base

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/fd86260a585f2cf69ca4e6fbc9bf03206f9b4f70/base

>---------------------------------------------------------------

commit fd86260a585f2cf69ca4e6fbc9bf03206f9b4f70
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date:   Sun Oct 20 23:44:29 2013 -0400

    Name change `CoercionT` to `CoercionType`, and addition of `repr`.
    
    `repr` converts a `(:~:)` to a `Coercion`. Name changes are as discussed
    on http://ghc.haskell.org/trac/ghc/wiki/TypeLevelNamingIssues


>---------------------------------------------------------------

fd86260a585f2cf69ca4e6fbc9bf03206f9b4f70
 Data/Type/Coercion.hs |   19 ++++++++++++-------
 1 file changed, 12 insertions(+), 7 deletions(-)

diff --git a/Data/Type/Coercion.hs b/Data/Type/Coercion.hs
index fbe055d..b595663 100644
--- a/Data/Type/Coercion.hs
+++ b/Data/Type/Coercion.hs
@@ -27,7 +27,8 @@ module Data.Type.Coercion
   , coerceWith
   , sym
   , trans
-  , CoercionT(..)
+  , repr
+  , CoercionType(..)
   ) where
 
 import qualified Data.Type.Equality as Eq
@@ -65,6 +66,10 @@ sym Coercion = unsym (coerce (Sym Coercion :: Sym a a))
 trans :: Coercion a b -> Coercion b c -> Coercion a c
 trans c Coercion = coerce c
 
+-- | Convert propositional (nominal) equality to representational equality
+repr :: (a Eq.:~: b) -> Coercion a b
+repr Eq.Refl = Coercion
+
 deriving instance Eq   (Coercion a b)
 deriving instance Show (Coercion a b)
 deriving instance Ord  (Coercion a b)
@@ -85,12 +90,12 @@ instance Coercible a b => Bounded (Coercion a b) where
 -- | 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 CoercionT f where
+class CoercionType f where
   -- | Conditionally prove the representational equality of @a@ and @b at .
-  coercionT :: f a -> f b -> Maybe (Coercion a b)
+  maybeCoercion :: f a -> f b -> Maybe (Coercion a b)
 
-instance CoercionT ((Eq.:~:) a) where
-  coercionT Eq.Refl Eq.Refl = Just Coercion
+instance CoercionType ((Eq.:~:) a) where
+  maybeCoercion Eq.Refl Eq.Refl = Just Coercion
 
-instance CoercionT (Coercion a) where
-  coercionT c Coercion = Just $ coerce (sym c)
+instance CoercionType (Coercion a) where
+  maybeCoercion c Coercion = Just $ coerce (sym c)



More information about the ghc-commits mailing list