[commit: ghc] master: Update Control.Monad.ST.* for Safe Haskell as now they're safe by default (065d433)

git at git.haskell.org git at git.haskell.org
Fri Nov 21 21:03:26 UTC 2014


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/065d43335c03a47f74b702ea1f64a41ddefeb8d3/ghc

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

commit 065d43335c03a47f74b702ea1f64a41ddefeb8d3
Author: David Terei <code at davidterei.com>
Date:   Wed Nov 19 17:58:43 2014 -0800

    Update Control.Monad.ST.* for Safe Haskell as now they're safe by default


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

065d43335c03a47f74b702ea1f64a41ddefeb8d3
 libraries/base/Control/Monad/ST.hs           | 4 ++--
 libraries/base/Control/Monad/ST/Lazy.hs      | 4 ++--
 libraries/base/Control/Monad/ST/Lazy/Imp.hs  | 2 +-
 libraries/base/Control/Monad/ST/Lazy/Safe.hs | 2 +-
 libraries/base/Control/Monad/ST/Safe.hs      | 2 +-
 libraries/base/Control/Monad/ST/Strict.hs    | 2 ++
 libraries/base/Data/STRef/Lazy.hs            | 2 +-
 7 files changed, 10 insertions(+), 8 deletions(-)

diff --git a/libraries/base/Control/Monad/ST.hs b/libraries/base/Control/Monad/ST.hs
index 0d2f58b..8313c2d 100644
--- a/libraries/base/Control/Monad/ST.hs
+++ b/libraries/base/Control/Monad/ST.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE Unsafe #-}
+{-# LANGUAGE Trustworthy #-}
 
 -----------------------------------------------------------------------------
 -- |
@@ -31,5 +31,5 @@ module Control.Monad.ST (
         stToIO,
     ) where
 
-import Control.Monad.ST.Safe
+import Control.Monad.ST.Imp
 
diff --git a/libraries/base/Control/Monad/ST/Lazy.hs b/libraries/base/Control/Monad/ST/Lazy.hs
index c212728..ef2e648 100644
--- a/libraries/base/Control/Monad/ST/Lazy.hs
+++ b/libraries/base/Control/Monad/ST/Lazy.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE Unsafe #-}
+{-# LANGUAGE Trustworthy #-}
 
 -----------------------------------------------------------------------------
 -- |
@@ -30,5 +30,5 @@ module Control.Monad.ST.Lazy (
         stToIO,
     ) where
 
-import Control.Monad.ST.Lazy.Safe
+import Control.Monad.ST.Lazy.Imp
 
diff --git a/libraries/base/Control/Monad/ST/Lazy/Imp.hs b/libraries/base/Control/Monad/ST/Lazy/Imp.hs
index 80c9fa5..55b28cf 100644
--- a/libraries/base/Control/Monad/ST/Lazy/Imp.hs
+++ b/libraries/base/Control/Monad/ST/Lazy/Imp.hs
@@ -38,7 +38,7 @@ module Control.Monad.ST.Lazy.Imp (
 
 import Control.Monad.Fix
 
-import qualified Control.Monad.ST.Safe as ST
+import qualified Control.Monad.ST as ST
 import qualified Control.Monad.ST.Unsafe as ST
 
 import qualified GHC.ST as GHC.ST
diff --git a/libraries/base/Control/Monad/ST/Lazy/Safe.hs b/libraries/base/Control/Monad/ST/Lazy/Safe.hs
index 387313f..9f8e606 100644
--- a/libraries/base/Control/Monad/ST/Lazy/Safe.hs
+++ b/libraries/base/Control/Monad/ST/Lazy/Safe.hs
@@ -18,7 +18,7 @@
 --
 -----------------------------------------------------------------------------
 
-module Control.Monad.ST.Lazy.Safe (
+module Control.Monad.ST.Lazy.Safe {-# DEPRECATED "Safe is now the default, please use Control.Monad.ST.Lazy instead" #-} (
         -- * The 'ST' monad
         ST,
         runST,
diff --git a/libraries/base/Control/Monad/ST/Safe.hs b/libraries/base/Control/Monad/ST/Safe.hs
index 1e9c981..d100832 100644
--- a/libraries/base/Control/Monad/ST/Safe.hs
+++ b/libraries/base/Control/Monad/ST/Safe.hs
@@ -18,7 +18,7 @@
 --
 -----------------------------------------------------------------------------
 
-module Control.Monad.ST.Safe (
+module Control.Monad.ST.Safe {-# DEPRECATED "Safe is now the default, please use Control.Monad.ST instead" #-} (
         -- * The 'ST' Monad
         ST,             -- abstract
         runST,
diff --git a/libraries/base/Control/Monad/ST/Strict.hs b/libraries/base/Control/Monad/ST/Strict.hs
index 4e474d9..c858548 100644
--- a/libraries/base/Control/Monad/ST/Strict.hs
+++ b/libraries/base/Control/Monad/ST/Strict.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE Safe #-}
+
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  Control.Monad.ST.Strict
diff --git a/libraries/base/Data/STRef/Lazy.hs b/libraries/base/Data/STRef/Lazy.hs
index 5134de4..c7c3291 100644
--- a/libraries/base/Data/STRef/Lazy.hs
+++ b/libraries/base/Data/STRef/Lazy.hs
@@ -23,7 +23,7 @@ module Data.STRef.Lazy (
         modifySTRef
  ) where
 
-import Control.Monad.ST.Lazy.Safe
+import Control.Monad.ST.Lazy
 import qualified Data.STRef as ST
 
 newSTRef    :: a -> ST s (ST.STRef s a)



More information about the ghc-commits mailing list