[commit: ghc] master: Add gcoerceWith to Data.Type.Coercion (113d50b)

git at git.haskell.org git at git.haskell.org
Thu Aug 18 13:12:36 UTC 2016


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/113d50b791c469394d38fab6ce5b760e5e8c35e2/ghc

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

commit 113d50b791c469394d38fab6ce5b760e5e8c35e2
Author: Ryan Scott <ryan.gl.scott at gmail.com>
Date:   Thu Aug 18 09:11:03 2016 -0400

    Add gcoerceWith to Data.Type.Coercion
    
    Summary:
    For symmetry with `gcastWith` in `Data.Type.Equality`.
    
    Fixes #12493.
    
    Test Plan: It compiles
    
    Reviewers: bgamari, goldfire, hvr, austin
    
    Subscribers: thomie
    
    Differential Revision: https://phabricator.haskell.org/D2456
    
    GHC Trac Issues: #12493


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

113d50b791c469394d38fab6ce5b760e5e8c35e2
 docs/users_guide/8.2.1-notes.rst     | 3 +++
 libraries/base/Data/Type/Coercion.hs | 8 ++++++++
 libraries/base/changelog.md          | 2 ++
 3 files changed, 13 insertions(+)

diff --git a/docs/users_guide/8.2.1-notes.rst b/docs/users_guide/8.2.1-notes.rst
index 27b49ef..0126427 100644
--- a/docs/users_guide/8.2.1-notes.rst
+++ b/docs/users_guide/8.2.1-notes.rst
@@ -100,6 +100,9 @@ See ``changelog.md`` in the ``base`` package for full release notes.
 
 - ``Data.Either`` now provides ``fromLeft`` and ``fromRight``
 
+- ``Data.Type.Coercion`` now provides ``gcoerceWith``, which is analogous to
+  ``gcastWith`` from ``Data.Type.Equality``.
+
 binary
 ~~~~~~
 
diff --git a/libraries/base/Data/Type/Coercion.hs b/libraries/base/Data/Type/Coercion.hs
index 254bb9a..318d098 100644
--- a/libraries/base/Data/Type/Coercion.hs
+++ b/libraries/base/Data/Type/Coercion.hs
@@ -7,6 +7,7 @@
 {-# LANGUAGE StandaloneDeriving  #-}
 {-# LANGUAGE NoImplicitPrelude   #-}
 {-# LANGUAGE PolyKinds           #-}
+{-# LANGUAGE RankNTypes          #-}
 
 -----------------------------------------------------------------------------
 -- |
@@ -25,6 +26,7 @@
 module Data.Type.Coercion
   ( Coercion(..)
   , coerceWith
+  , gcoerceWith
   , sym
   , trans
   , repr
@@ -56,6 +58,12 @@ data Coercion a b where
 coerceWith :: Coercion a b -> a -> b
 coerceWith Coercion x = coerce x
 
+-- | Generalized form of type-safe cast using representational equality
+--
+-- @since 4.10.0.0
+gcoerceWith :: Coercion a b -> (Coercible a b => r) -> r
+gcoerceWith Coercion x = x
+
 -- | Symmetry of representational equality
 sym :: Coercion a b -> Coercion b a
 sym Coercion = Coercion
diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md
index 996456f..f8f6b10 100644
--- a/libraries/base/changelog.md
+++ b/libraries/base/changelog.md
@@ -16,6 +16,8 @@
 
   * `Data.Either` now provides `fromLeft` and `fromRight` (#12402)
 
+  * `Data.Type.Coercion` now provides `gcoerceWith` (#12493)
+
 ## 4.9.0.0  *May 2016*
 
   * Bundled with GHC 8.0



More information about the ghc-commits mailing list