summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorIan Lynagh <igloo@earth.li>2008-08-23 22:30:14 +0000
committerIan Lynagh <igloo@earth.li>2008-08-23 22:30:14 +0000
commit75097ac2585560aa580563d4c7be0b1944a41911 (patch)
tree48105e163f657df2cace20bb76559effa6907034
parent7166d891f0f9142405f0cb6374836b2ebb55e5c2 (diff)
downloadhaskell-75097ac2585560aa580563d4c7be0b1944a41911.tar.gz
Remove ST stuff that is now in the new st package
-rw-r--r--libraries/base/Control/Monad/ST.hs65
-rw-r--r--libraries/base/Control/Monad/ST/Lazy.hs152
-rw-r--r--libraries/base/Control/Monad/ST/Strict.hs20
-rw-r--r--libraries/base/Data/STRef.hs41
-rw-r--r--libraries/base/Data/STRef/Lazy.hs34
-rw-r--r--libraries/base/Data/STRef/Strict.hs20
-rw-r--r--libraries/base/base.cabal6
7 files changed, 0 insertions, 338 deletions
diff --git a/libraries/base/Control/Monad/ST.hs b/libraries/base/Control/Monad/ST.hs
deleted file mode 100644
index b77966484f..0000000000
--- a/libraries/base/Control/Monad/ST.hs
+++ /dev/null
@@ -1,65 +0,0 @@
-{-# OPTIONS_GHC -fno-warn-orphans #-}
------------------------------------------------------------------------------
--- |
--- Module : Control.Monad.ST
--- Copyright : (c) The University of Glasgow 2001
--- License : BSD-style (see the file libraries/base/LICENSE)
---
--- Maintainer : libraries@haskell.org
--- Stability : experimental
--- Portability : non-portable (requires universal quantification for runST)
---
--- This library provides support for /strict/ state threads, as
--- described in the PLDI \'94 paper by John Launchbury and Simon Peyton
--- Jones /Lazy Functional State Threads/.
---
------------------------------------------------------------------------------
-
-module Control.Monad.ST
- (
- -- * The 'ST' Monad
- ST, -- abstract, instance of Functor, Monad, Typeable.
- runST, -- :: (forall s. ST s a) -> a
- fixST, -- :: (a -> ST s a) -> ST s a
-
- -- * Converting 'ST' to 'IO'
- RealWorld, -- abstract
- stToIO, -- :: ST RealWorld a -> IO a
-
- -- * Unsafe operations
- unsafeInterleaveST, -- :: ST s a -> ST s a
- unsafeIOToST, -- :: IO a -> ST s a
- unsafeSTToIO -- :: ST s a -> IO a
- ) where
-
-import Prelude
-
-import Control.Monad.Fix
-
-#include "Typeable.h"
-
-#ifdef __HUGS__
-import Data.Typeable
-import Hugs.ST
-import qualified Hugs.LazyST as LazyST
-
-INSTANCE_TYPEABLE2(ST,sTTc,"ST")
-INSTANCE_TYPEABLE0(RealWorld,realWorldTc,"RealWorld")
-
-fixST :: (a -> ST s a) -> ST s a
-fixST f = LazyST.lazyToStrictST (LazyST.fixST (LazyST.strictToLazyST . f))
-
-unsafeInterleaveST :: ST s a -> ST s a
-unsafeInterleaveST =
- LazyST.lazyToStrictST . LazyST.unsafeInterleaveST . LazyST.strictToLazyST
-#endif
-
-#ifdef __GLASGOW_HASKELL__
-import GHC.ST ( ST, runST, fixST, unsafeInterleaveST )
-import GHC.Base ( RealWorld )
-import GHC.IOBase ( stToIO, unsafeIOToST, unsafeSTToIO )
-#endif
-
-instance MonadFix (ST s) where
- mfix = fixST
-
diff --git a/libraries/base/Control/Monad/ST/Lazy.hs b/libraries/base/Control/Monad/ST/Lazy.hs
deleted file mode 100644
index 00aa4f06d5..0000000000
--- a/libraries/base/Control/Monad/ST/Lazy.hs
+++ /dev/null
@@ -1,152 +0,0 @@
------------------------------------------------------------------------------
--- |
--- Module : Control.Monad.ST.Lazy
--- Copyright : (c) The University of Glasgow 2001
--- License : BSD-style (see the file libraries/base/LICENSE)
---
--- Maintainer : libraries@haskell.org
--- Stability : provisional
--- Portability : non-portable (requires universal quantification for runST)
---
--- This module presents an identical interface to "Control.Monad.ST",
--- except that the monad delays evaluation of state operations until
--- a value depending on them is required.
---
------------------------------------------------------------------------------
-
-module Control.Monad.ST.Lazy (
- -- * The 'ST' monad
- ST,
- runST,
- fixST,
-
- -- * Converting between strict and lazy 'ST'
- strictToLazyST, lazyToStrictST,
-
- -- * Converting 'ST' To 'IO'
- RealWorld,
- stToIO,
-
- -- * Unsafe operations
- unsafeInterleaveST,
- unsafeIOToST
- ) where
-
-import Prelude
-
-import Control.Monad.Fix
-
-import Control.Monad.ST (RealWorld)
-import qualified Control.Monad.ST as ST
-
-#ifdef __GLASGOW_HASKELL__
-import qualified GHC.ST
-import GHC.Base
-import Control.Monad
-#endif
-
-#ifdef __HUGS__
-import Hugs.LazyST
-#endif
-
-#ifdef __GLASGOW_HASKELL__
--- | The lazy state-transformer monad.
--- A computation of type @'ST' s a@ transforms an internal state indexed
--- by @s@, and returns a value of type @a@.
--- The @s@ parameter is either
---
--- * an unstantiated type variable (inside invocations of 'runST'), or
---
--- * 'RealWorld' (inside invocations of 'stToIO').
---
--- It serves to keep the internal states of different invocations of
--- 'runST' separate from each other and from invocations of 'stToIO'.
---
--- The '>>=' and '>>' operations are not strict in the state. For example,
---
--- @'runST' (writeSTRef _|_ v >>= readSTRef _|_ >> return 2) = 2@
-newtype ST s a = ST (State s -> (a, State s))
-data State s = S# (State# s)
-
-instance Functor (ST s) where
- fmap f m = ST $ \ s ->
- let
- ST m_a = m
- (r,new_s) = m_a s
- in
- (f r,new_s)
-
-instance Monad (ST s) where
-
- return a = ST $ \ s -> (a,s)
- m >> k = m >>= \ _ -> k
- fail s = error s
-
- (ST m) >>= k
- = ST $ \ s ->
- let
- (r,new_s) = m s
- ST k_a = k r
- in
- k_a new_s
-
-{-# NOINLINE runST #-}
--- | Return the value computed by a state transformer computation.
--- The @forall@ ensures that the internal state used by the 'ST'
--- computation is inaccessible to the rest of the program.
-runST :: (forall s. ST s a) -> a
-runST st = case st of ST the_st -> let (r,_) = the_st (S# realWorld#) in r
-
--- | Allow the result of a state transformer computation to be used (lazily)
--- inside the computation.
--- Note that if @f@ is strict, @'fixST' f = _|_@.
-fixST :: (a -> ST s a) -> ST s a
-fixST m = ST (\ s ->
- let
- ST m_r = m r
- (r,s') = m_r s
- in
- (r,s'))
-#endif
-
-instance MonadFix (ST s) where
- mfix = fixST
-
--- ---------------------------------------------------------------------------
--- Strict <--> Lazy
-
-#ifdef __GLASGOW_HASKELL__
-{-|
-Convert a strict 'ST' computation into a lazy one. The strict state
-thread passed to 'strictToLazyST' is not performed until the result of
-the lazy state thread it returns is demanded.
--}
-strictToLazyST :: ST.ST s a -> ST s a
-strictToLazyST m = ST $ \s ->
- let
- pr = case s of { S# s# -> GHC.ST.liftST m s# }
- r = case pr of { GHC.ST.STret _ v -> v }
- s' = case pr of { GHC.ST.STret s2# _ -> S# s2# }
- in
- (r, s')
-
-{-|
-Convert a lazy 'ST' computation into a strict one.
--}
-lazyToStrictST :: ST s a -> ST.ST s a
-lazyToStrictST (ST m) = GHC.ST.ST $ \s ->
- case (m (S# s)) of (a, S# s') -> (# s', a #)
-
-unsafeInterleaveST :: ST s a -> ST s a
-unsafeInterleaveST = strictToLazyST . ST.unsafeInterleaveST . lazyToStrictST
-#endif
-
-unsafeIOToST :: IO a -> ST s a
-unsafeIOToST = strictToLazyST . ST.unsafeIOToST
-
--- | A monad transformer embedding lazy state transformers in the 'IO'
--- monad. The 'RealWorld' parameter indicates that the internal state
--- used by the 'ST' computation is a special one supplied by the 'IO'
--- monad, and thus distinct from those used by invocations of 'runST'.
-stToIO :: ST RealWorld a -> IO a
-stToIO = ST.stToIO . lazyToStrictST
diff --git a/libraries/base/Control/Monad/ST/Strict.hs b/libraries/base/Control/Monad/ST/Strict.hs
deleted file mode 100644
index a899616f55..0000000000
--- a/libraries/base/Control/Monad/ST/Strict.hs
+++ /dev/null
@@ -1,20 +0,0 @@
------------------------------------------------------------------------------
--- |
--- Module : Control.Monad.ST.Strict
--- Copyright : (c) The University of Glasgow 2001
--- License : BSD-style (see the file libraries/base/LICENSE)
---
--- Maintainer : libraries@haskell.org
--- Stability : provisional
--- Portability : non-portable (requires universal quantification for runST)
---
--- The strict ST monad (re-export of "Control.Monad.ST")
---
------------------------------------------------------------------------------
-
-module Control.Monad.ST.Strict (
- module Control.Monad.ST
- ) where
-
-import Prelude
-import Control.Monad.ST
diff --git a/libraries/base/Data/STRef.hs b/libraries/base/Data/STRef.hs
deleted file mode 100644
index 288cbe778f..0000000000
--- a/libraries/base/Data/STRef.hs
+++ /dev/null
@@ -1,41 +0,0 @@
------------------------------------------------------------------------------
--- |
--- Module : Data.STRef
--- Copyright : (c) The University of Glasgow 2001
--- License : BSD-style (see the file libraries/base/LICENSE)
---
--- Maintainer : libraries@haskell.org
--- Stability : experimental
--- Portability : non-portable (uses Control.Monad.ST)
---
--- Mutable references in the (strict) ST monad.
---
------------------------------------------------------------------------------
-
-module Data.STRef (
- -- * STRefs
- STRef, -- abstract, instance Eq
- newSTRef, -- :: a -> ST s (STRef s a)
- readSTRef, -- :: STRef s a -> ST s a
- writeSTRef, -- :: STRef s a -> a -> ST s ()
- modifySTRef -- :: STRef s a -> (a -> a) -> ST s ()
- ) where
-
-import Prelude
-
-#ifdef __GLASGOW_HASKELL__
-import GHC.ST
-import GHC.STRef
-#endif
-
-#ifdef __HUGS__
-import Hugs.ST
-import Data.Typeable
-
-#include "Typeable.h"
-INSTANCE_TYPEABLE2(STRef,stRefTc,"STRef")
-#endif
-
--- |Mutate the contents of an 'STRef'
-modifySTRef :: STRef s a -> (a -> a) -> ST s ()
-modifySTRef ref f = writeSTRef ref . f =<< readSTRef ref
diff --git a/libraries/base/Data/STRef/Lazy.hs b/libraries/base/Data/STRef/Lazy.hs
deleted file mode 100644
index 3218310667..0000000000
--- a/libraries/base/Data/STRef/Lazy.hs
+++ /dev/null
@@ -1,34 +0,0 @@
------------------------------------------------------------------------------
--- |
--- Module : Data.STRef.Lazy
--- Copyright : (c) The University of Glasgow 2001
--- License : BSD-style (see the file libraries/base/LICENSE)
---
--- Maintainer : libraries@haskell.org
--- Stability : experimental
--- Portability : non-portable (uses Control.Monad.ST.Lazy)
---
--- Mutable references in the lazy ST monad.
---
------------------------------------------------------------------------------
-module Data.STRef.Lazy (
- -- * STRefs
- ST.STRef, -- abstract, instance Eq
- newSTRef, -- :: a -> ST s (STRef s a)
- readSTRef, -- :: STRef s a -> ST s a
- writeSTRef, -- :: STRef s a -> a -> ST s ()
- modifySTRef -- :: STRef s a -> (a -> a) -> ST s ()
- ) where
-
-import Control.Monad.ST.Lazy
-import qualified Data.STRef as ST
-
-newSTRef :: a -> ST s (ST.STRef s a)
-readSTRef :: ST.STRef s a -> ST s a
-writeSTRef :: ST.STRef s a -> a -> ST s ()
-modifySTRef :: ST.STRef s a -> (a -> a) -> ST s ()
-
-newSTRef = strictToLazyST . ST.newSTRef
-readSTRef = strictToLazyST . ST.readSTRef
-writeSTRef r a = strictToLazyST (ST.writeSTRef r a)
-modifySTRef r f = strictToLazyST (ST.modifySTRef r f)
diff --git a/libraries/base/Data/STRef/Strict.hs b/libraries/base/Data/STRef/Strict.hs
deleted file mode 100644
index 61ac9b8ea8..0000000000
--- a/libraries/base/Data/STRef/Strict.hs
+++ /dev/null
@@ -1,20 +0,0 @@
------------------------------------------------------------------------------
--- |
--- Module : Data.STRef.Strict
--- Copyright : (c) The University of Glasgow 2001
--- License : BSD-style (see the file libraries/base/LICENSE)
---
--- Maintainer : libraries@haskell.org
--- Stability : provisional
--- Portability : non-portable (uses Control.Monad.ST.Strict)
---
--- Mutable references in the (strict) ST monad (re-export of "Data.STRef")
---
------------------------------------------------------------------------------
-
-module Data.STRef.Strict (
- module Data.STRef
- ) where
-
-import Prelude
-import Data.STRef
diff --git a/libraries/base/base.cabal b/libraries/base/base.cabal
index 78710470dc..015116714c 100644
--- a/libraries/base/base.cabal
+++ b/libraries/base/base.cabal
@@ -84,9 +84,6 @@ Library {
Control.Monad,
Control.Monad.Fix,
Control.Monad.Instances,
- Control.Monad.ST,
- Control.Monad.ST.Lazy,
- Control.Monad.ST.Strict,
Data.Bits,
Data.Bool,
Data.Char,
@@ -106,9 +103,6 @@ Library {
Data.Monoid,
Data.Ord,
Data.Ratio,
- Data.STRef,
- Data.STRef.Lazy,
- Data.STRef.Strict,
Data.String,
Data.Traversable
Data.Tuple,