[commit: base] master: Remove some functions deprecated since GHC 7.2. (b3242be)
Ian Lynagh
igloo at earth.li
Fri Mar 1 16:20:40 CET 2013
Repository : ssh://darcs.haskell.org//srv/darcs/packages/base
On branch : master
http://hackage.haskell.org/trac/ghc/changeset/b3242beb894061ac35cc6b803bcc26644a7d1bf7
>---------------------------------------------------------------
commit b3242beb894061ac35cc6b803bcc26644a7d1bf7
Author: Ian Lynagh <ian at well-typed.com>
Date: Fri Mar 1 14:02:24 2013 +0000
Remove some functions deprecated since GHC 7.2.
>---------------------------------------------------------------
Control/Monad/ST.hs | 20 --------------------
Control/Monad/ST/Lazy.hs | 15 ---------------
2 files changed, 0 insertions(+), 35 deletions(-)
diff --git a/Control/Monad/ST.hs b/Control/Monad/ST.hs
index 6113055..0d2f58b 100644
--- a/Control/Monad/ST.hs
+++ b/Control/Monad/ST.hs
@@ -29,27 +29,7 @@ module Control.Monad.ST (
-- * Converting 'ST' to 'IO'
RealWorld, -- abstract
stToIO,
-
- -- * Unsafe Functions
- unsafeInterleaveST,
- unsafeIOToST,
- unsafeSTToIO
) where
import Control.Monad.ST.Safe
-import qualified Control.Monad.ST.Unsafe as U
-
-{-# DEPRECATED unsafeInterleaveST, unsafeIOToST, unsafeSTToIO "Please import from Control.Monad.ST.Unsafe instead; This will be removed in the next release" #-} -- deprecated in 7.2
-
-{-# INLINE unsafeInterleaveST #-}
-unsafeInterleaveST :: ST s a -> ST s a
-unsafeInterleaveST = U.unsafeInterleaveST
-
-{-# INLINE unsafeIOToST #-}
-unsafeIOToST :: IO a -> ST s a
-unsafeIOToST = U.unsafeIOToST
-
-{-# INLINE unsafeSTToIO #-}
-unsafeSTToIO :: ST s a -> IO a
-unsafeSTToIO = U.unsafeSTToIO
diff --git a/Control/Monad/ST/Lazy.hs b/Control/Monad/ST/Lazy.hs
index 26effa4..c212728 100644
--- a/Control/Monad/ST/Lazy.hs
+++ b/Control/Monad/ST/Lazy.hs
@@ -28,22 +28,7 @@ module Control.Monad.ST.Lazy (
-- * Converting 'ST' To 'IO'
RealWorld,
stToIO,
-
- -- * Unsafe Functions
- unsafeInterleaveST,
- unsafeIOToST
) where
import Control.Monad.ST.Lazy.Safe
-import qualified Control.Monad.ST.Lazy.Unsafe as U
-
-{-# DEPRECATED unsafeInterleaveST, unsafeIOToST "Please import from Control.Monad.ST.Lazy.Unsafe instead; This will be removed in the next release" #-} -- deprecated in 7.2
-
-{-# INLINE unsafeInterleaveST #-}
-unsafeInterleaveST :: ST s a -> ST s a
-unsafeInterleaveST = U.unsafeInterleaveST
-
-{-# INLINE unsafeIOToST #-}
-unsafeIOToST :: IO a -> ST s a
-unsafeIOToST = U.unsafeIOToST
More information about the ghc-commits
mailing list