[commit: packages/base] ghc-7.8: Create Data.Coerce (#8745) (a265d59)

git at git.haskell.org git at git.haskell.org
Fri Feb 28 23:39:35 UTC 2014


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

On branch  : ghc-7.8
Link       : http://ghc.haskell.org/trac/ghc/changeset/a265d59e8a2761d44d3621dd67cb865271b5d00e/base

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

commit a265d59e8a2761d44d3621dd67cb865271b5d00e
Author: Austin Seipp <austin at well-typed.com>
Date:   Fri Feb 28 11:50:30 2014 -0600

    Create Data.Coerce (#8745)
    
    Data.Coerce is a Trustworthy module which safely exports both
    `Coercible` and `coerce` for use by users, as it can now be considered
    safe under role checking.
    
    See the ticket for details.
    
    Signed-off-by: Austin Seipp <austin at well-typed.com>
    
    (cherry picked from commit f932b79948f0f8e2ac354cdcaea21c5b7c59a27a)


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

a265d59e8a2761d44d3621dd67cb865271b5d00e
 Control/Monad/ST/Strict.hs => Data/Coerce.hs |   21 ++++++++++++---------
 GHC/Exts.hs                                  |    6 +++---
 base.cabal                                   |    1 +
 3 files changed, 16 insertions(+), 12 deletions(-)

diff --git a/Control/Monad/ST/Strict.hs b/Data/Coerce.hs
similarity index 52%
copy from Control/Monad/ST/Strict.hs
copy to Data/Coerce.hs
index 4e474d9..93d5e19 100644
--- a/Control/Monad/ST/Strict.hs
+++ b/Data/Coerce.hs
@@ -1,20 +1,23 @@
+{-# LANGUAGE Trustworthy #-}
+{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE StandaloneDeriving #-}
+
 -----------------------------------------------------------------------------
 -- |
--- Module      :  Control.Monad.ST.Strict
+-- Module      :  Data.Coerce
 -- Copyright   :  (c) The University of Glasgow 2001
 -- License     :  BSD-style (see the file libraries/base/LICENSE)
 --
 -- Maintainer  :  libraries at haskell.org
 -- Stability   :  provisional
--- Portability :  non-portable (requires universal quantification for runST)
+-- Portability :  portable
 --
--- The strict ST monad (re-export of "Control.Monad.ST")
+-- Safe coercions between data types.
 --
 -----------------------------------------------------------------------------
 
-module Control.Monad.ST.Strict (
-        module Control.Monad.ST
-  ) where
-
-import Control.Monad.ST
-
+module Data.Coerce
+        ( -- * Safe coercions
+          coerce, Coercible,
+        ) where
+import GHC.Prim (coerce, Coercible)
diff --git a/GHC/Exts.hs b/GHC/Exts.hs
index 299adab..62f1951 100755
--- a/GHC/Exts.hs
+++ b/GHC/Exts.hs
@@ -46,7 +46,7 @@ module GHC.Exts
         lazy, inline,
 
         -- * Safe coercions
-        GHC.Prim.coerce, GHC.Prim.Coercible,
+        Data.Coerce.coerce, Data.Coerce.Coercible,
 
         -- * Transform comprehensions
         Down(..), groupWith, sortWith, the,
@@ -70,12 +70,12 @@ module GHC.Exts
 import Prelude
 
 import GHC.Prim hiding (coerce, Coercible)
-import qualified GHC.Prim
-import GHC.Base hiding (coerce, Coercible)
+import GHC.Base hiding (coerce, Coercible) -- implicitly comes from GHC.Prim
 import GHC.Word
 import GHC.Int
 import GHC.Ptr
 import GHC.Stack
+import qualified Data.Coerce
 import Data.String
 import Data.List
 import Data.Data
diff --git a/base.cabal b/base.cabal
index 5c04513..f8937dc 100644
--- a/base.cabal
+++ b/base.cabal
@@ -118,6 +118,7 @@ Library
         Data.Bits
         Data.Bool
         Data.Char
+        Data.Coerce
         Data.Complex
         Data.Data
         Data.Dynamic



More information about the ghc-commits mailing list