diff options
Diffstat (limited to 'libraries/base')
-rw-r--r-- | libraries/base/Control/Monad.hs | 2 | ||||
-rw-r--r-- | libraries/base/Control/Monad/ST/Imp.hs | 2 | ||||
-rw-r--r-- | libraries/base/Control/Monad/ST/Lazy/Imp.hs | 16 | ||||
-rw-r--r-- | libraries/base/Control/Monad/ST/Lazy/Safe.hs | 2 | ||||
-rw-r--r-- | libraries/base/Control/Monad/ST/Lazy/Unsafe.hs | 2 | ||||
-rw-r--r-- | libraries/base/Data/Functor/Utils.hs | 4 | ||||
-rwxr-xr-x | libraries/base/GHC/Exts.hs | 2 | ||||
-rw-r--r-- | libraries/base/GHC/IO.hs | 14 | ||||
-rw-r--r-- | libraries/base/GHC/ST.hs | 12 |
9 files changed, 28 insertions, 28 deletions
diff --git a/libraries/base/Control/Monad.hs b/libraries/base/Control/Monad.hs index 08c85a8b9b..96d8938101 100644 --- a/libraries/base/Control/Monad.hs +++ b/libraries/base/Control/Monad.hs @@ -188,7 +188,7 @@ forever a = let a' = a *> a' in a' -- | The 'mapAndUnzipM' function maps its first argument over a list, returning -- the result as a pair of lists. This function is mainly used with complicated --- data structures or a state-transforming monad. +-- data structures or a state monad. mapAndUnzipM :: (Applicative m) => (a -> m (b,c)) -> [a] -> m ([b], [c]) {-# INLINE mapAndUnzipM #-} mapAndUnzipM f xs = unzip <$> traverse f xs diff --git a/libraries/base/Control/Monad/ST/Imp.hs b/libraries/base/Control/Monad/ST/Imp.hs index 8ba51e86f0..55bd780f2c 100644 --- a/libraries/base/Control/Monad/ST/Imp.hs +++ b/libraries/base/Control/Monad/ST/Imp.hs @@ -45,7 +45,7 @@ import Control.Exception.Base ( catch, throwIO, NonTermination (..) , BlockedIndefinitelyOnMVar (..) ) --- | Allow the result of a state transformer computation to be used (lazily) +-- | Allow the result of an 'ST' computation to be used (lazily) -- inside the computation. -- -- Note that if @f@ is strict, @'fixST' f = _|_@. diff --git a/libraries/base/Control/Monad/ST/Lazy/Imp.hs b/libraries/base/Control/Monad/ST/Lazy/Imp.hs index 4f1204b89f..699c81e258 100644 --- a/libraries/base/Control/Monad/ST/Lazy/Imp.hs +++ b/libraries/base/Control/Monad/ST/Lazy/Imp.hs @@ -14,7 +14,7 @@ -- 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 +-- except that the monad delays evaluation of 'ST' operations until -- a value depending on them is required. -- ----------------------------------------------------------------------------- @@ -46,10 +46,10 @@ import qualified GHC.ST as GHC.ST import GHC.Base import qualified Control.Monad.Fail as Fail --- | 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 +-- | The lazy @'ST' monad. +-- The ST monad allows for destructive updates, but is escapable (unlike IO). +-- A computation of type @'ST' s a@ returns a value of type @a@, and +-- execute in "thread" @s@. The @s@ parameter is either -- -- * an uninstantiated type variable (inside invocations of 'runST'), or -- @@ -198,13 +198,13 @@ instance Monad (ST s) where instance Fail.MonadFail (ST s) where fail s = errorWithoutStackTrace s --- | Return the value computed by a state transformer computation. +-- | Return the value computed by an 'ST' 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 st) = runRW# (\s -> case st (S# s) of (r, _) -> r) --- | Allow the result of a state transformer computation to be used (lazily) +-- | Allow the result of an 'ST' computation to be used (lazily) -- inside the computation. -- Note that if @f@ is strict, @'fixST' f = _|_@. fixST :: (a -> ST s a) -> ST s a @@ -243,7 +243,7 @@ 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 #) --- | A monad transformer embedding lazy state transformers in the 'IO' +-- | A monad transformer embedding lazy 'ST' 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'. diff --git a/libraries/base/Control/Monad/ST/Lazy/Safe.hs b/libraries/base/Control/Monad/ST/Lazy/Safe.hs index 9f8e60686f..05aaae7523 100644 --- a/libraries/base/Control/Monad/ST/Lazy/Safe.hs +++ b/libraries/base/Control/Monad/ST/Lazy/Safe.hs @@ -11,7 +11,7 @@ -- 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 +-- except that the monad delays evaluation of 'ST' operations until -- a value depending on them is required. -- -- Safe API only. diff --git a/libraries/base/Control/Monad/ST/Lazy/Unsafe.hs b/libraries/base/Control/Monad/ST/Lazy/Unsafe.hs index 4a1b8c79a6..be31c93c24 100644 --- a/libraries/base/Control/Monad/ST/Lazy/Unsafe.hs +++ b/libraries/base/Control/Monad/ST/Lazy/Unsafe.hs @@ -11,7 +11,7 @@ -- 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 +-- except that the monad delays evaluation of 'ST' operations until -- a value depending on them is required. -- -- Unsafe API. diff --git a/libraries/base/Data/Functor/Utils.hs b/libraries/base/Data/Functor/Utils.hs index c6c2758c9d..57e75424da 100644 --- a/libraries/base/Data/Functor/Utils.hs +++ b/libraries/base/Data/Functor/Utils.hs @@ -48,7 +48,7 @@ instance Ord a => Semigroup (Min a) where instance Ord a => Monoid (Min a) where mempty = Min Nothing --- left-to-right state transformer +-- left-to-right state-transforming monad newtype StateL s a = StateL { runStateL :: s -> (s, a) } -- | @since 4.0 @@ -67,7 +67,7 @@ instance Applicative (StateL s) where (s'', y) = ky s' in (s'', f x y) --- right-to-left state transformer +-- right-to-left state-transforming monad newtype StateR s a = StateR { runStateR :: s -> (s, a) } -- | @since 4.0 diff --git a/libraries/base/GHC/Exts.hs b/libraries/base/GHC/Exts.hs index 3f5b630ab9..9fc1a638fc 100755 --- a/libraries/base/GHC/Exts.hs +++ b/libraries/base/GHC/Exts.hs @@ -49,7 +49,7 @@ module GHC.Exts -- * Ids with special behaviour lazy, inline, oneShot, - -- * Running 'RealWorld' state transformers + -- * Running 'RealWorld' state thread runRW#, -- * Safe coercions diff --git a/libraries/base/GHC/IO.hs b/libraries/base/GHC/IO.hs index 05ad277127..6b83cca0d1 100644 --- a/libraries/base/GHC/IO.hs +++ b/libraries/base/GHC/IO.hs @@ -53,8 +53,8 @@ import {-# SOURCE #-} GHC.IO.Exception ( userError, IOError ) -- The IO Monad {- -The IO Monad is just an instance of the ST monad, where the state is -the real world. We use the exception mechanism (in GHC.Exception) to +The IO Monad is just an instance of the ST monad, where the state thread +is the real world. We use the exception mechanism (in GHC.Exception) to implement IO exceptions. NOTE: The IO representation is deeply wired in to various parts of the @@ -84,7 +84,7 @@ failIO s = IO (raiseIO# (toException (userError s))) -- --------------------------------------------------------------------------- -- Coercions between IO and ST --- | Embed a strict state transformer in an 'IO' +-- | Embed a strict state thread in an 'IO' -- action. 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'. @@ -92,20 +92,20 @@ stToIO :: ST RealWorld a -> IO a stToIO (ST m) = IO m -- | Convert an 'IO' action into an 'ST' action. The type of the result --- is constrained to use a 'RealWorld' state, and therefore the result cannot --- be passed to 'runST'. +-- is constrained to use a 'RealWorld' state thread, and therefore the +-- result cannot be passed to 'runST'. ioToST :: IO a -> ST RealWorld a ioToST (IO m) = (ST m) -- | Convert an 'IO' action to an 'ST' action. -- This relies on 'IO' and 'ST' having the same representation modulo the --- constraint on the type of the state. +-- constraint on the state thread type parameter. unsafeIOToST :: IO a -> ST s a unsafeIOToST (IO io) = ST $ \ s -> (unsafeCoerce# io) s -- | Convert an 'ST' action to an 'IO' action. -- This relies on 'IO' and 'ST' having the same representation modulo the --- constraint on the type of the state. +-- constraint on the state thread type parameter. -- -- For an example demonstrating why this is unsafe, see -- https://mail.haskell.org/pipermail/haskell-cafe/2009-April/060719.html diff --git a/libraries/base/GHC/ST.hs b/libraries/base/GHC/ST.hs index 9a174383f8..ccc123d303 100644 --- a/libraries/base/GHC/ST.hs +++ b/libraries/base/GHC/ST.hs @@ -30,13 +30,13 @@ import qualified Control.Monad.Fail as Fail default () --- The state-transformer monad proper. By default the monad is strict; +-- The 'ST' monad proper. By default the monad is strict; -- too many people got bitten by space leaks when it was lazy. --- | The strict 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 +-- | The strict 'ST' monad. +-- The 'ST' monad allows for destructive updates, but is escapable (unlike IO). +-- A computation of type @'ST' s a@ returns a value of type @a@, and +-- execute in "thread" @s@. The @s@ parameter is either -- -- * an uninstantiated type variable (inside invocations of 'runST'), or -- @@ -131,7 +131,7 @@ instance Show (ST s a) where showList = showList__ (showsPrec 0) {-# INLINE runST #-} --- | Return the value computed by a state transformer computation. +-- | Return the value computed by a state thread. -- 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 |