diff --git a/Control/Monad/Trans/Accum.hs b/Control/Monad/Trans/Accum.hs index e5b7b88c08a81f2fcea888d20b4517f6923efd95..61ac250602681e64a090055b04879e6ed674badc 100644 --- a/Control/Monad/Trans/Accum.hs +++ b/Control/Monad/Trans/Accum.hs @@ -18,10 +18,12 @@ -- -- The lazy 'AccumT' monad transformer, which adds accumulation -- capabilities (such as declarations or document patches) to a given monad. +-- Each computation has access to the combination of the input environment +-- and outputs added so far, and returns the outputs added. -- --- This monad transformer provides append-only accumulation --- during the computation. For more general access, use --- "Control.Monad.Trans.State" instead. +-- In applications requiring only the ability to accumulate an output and +-- to inspect the output so far, it would be considerably more efficient +-- to use "Control.Monad.Trans.State" instead. ----------------------------------------------------------------------------- module Control.Monad.Trans.Accum ( @@ -78,8 +80,16 @@ import GHC.Generics -- --------------------------------------------------------------------------- -- | An accumulation monad parameterized by the type @w@ of output to accumulate. -- --- The 'return' function produces the output 'mempty', while @>>=@ --- combines the outputs of the subcomputations using 'mappend'. +-- This monad is a more complex extension of both the reader and writer +-- monads. The 'return' function produces the output 'mempty', while @m +-- '>>=' k@ uses the output of @m@ both to extend the initial environment +-- of @k@ and to combine with the output of @k@: +-- +-- <<images/bind-AccumT.svg>> +-- +-- In applications requiring only the ability to accumulate an output and +-- to inspect the output so far, it would be considerably more efficient +-- to use a state monad. type Accum w = AccumT w Identity -- | Construct an accumulation computation from a (result, output) pair. @@ -124,21 +134,28 @@ mapAccum f = mapAccumT (Identity . f . runIdentity) -- -- * @m@ - The inner monad. -- --- The 'return' function produces the output 'mempty', while @>>=@ --- combines the outputs of the subcomputations using 'mappend'. --- --- This monad transformer is similar to both state and writer monad transformers. --- Thus it can be seen as +-- This monad transformer is a more complex extension of both the reader +-- and writer monad transformers. The 'return' function produces the +-- output 'mempty', while @m '>>=' k@ uses the output of @m@ both to +-- extend the initial environment of @k@ and to combine with the output +-- of @k@: -- --- * a restricted append-only version of a state monad transformer or +-- <<images/bind-AccumT.svg>> -- --- * a writer monad transformer with the extra ability to read all previous output. +-- In applications requiring only the ability to accumulate an output and +-- to inspect the output so far, it would be considerably more efficient +-- to use a state monad transformer. newtype AccumT w m a = AccumT (w -> m (a, w)) #if __GLASGOW_HASKELL__ >= 704 deriving (Generic) #endif --- | Unwrap an accumulation computation. +-- | Unwrap an accumulation computation. For example, in the call +-- +-- @ (value, locals) <- runAccumT action globals@ +-- +-- the action is fed an initial environment @globals@, and @locals@ is +-- the sum of all arguments to calls of 'add' executed by the action. runAccumT :: AccumT w m a -> w -> m (a, w) runAccumT (AccumT f) = f {-# INLINE runAccumT #-} @@ -152,8 +169,8 @@ execAccumT m w = do return w' {-# INLINE execAccumT #-} --- | Evaluate an accumulation computation with the given initial output history --- and return the final value, discarding the final output. +-- | Evaluate an accumulation computation with the given initial output +-- history and return the final value, discarding the final output. -- -- * @'evalAccumT' m w = 'liftM' 'fst' ('runAccumT' m w)@ evalAccumT :: (Monad m, Monoid w) => AccumT w m a -> w -> m a @@ -162,8 +179,8 @@ evalAccumT m w = do return a {-# INLINE evalAccumT #-} --- | Map both the return value and output of a computation using --- the given function. +-- | Map both the return value and output of a computation using the +-- given function. -- -- * @'runAccumT' ('mapAccumT' f m) = f . 'runAccumT' m@ mapAccumT :: (m (a, w) -> n (b, w)) -> AccumT w m a -> AccumT w n b diff --git a/Control/Monad/Trans/Reader.hs b/Control/Monad/Trans/Reader.hs index fd9419d7aa52e4148dda56710fc3c2ea095f2f41..86bf311541dc31bc2ab2c4255176a400e3d7f331 100644 --- a/Control/Monad/Trans/Reader.hs +++ b/Control/Monad/Trans/Reader.hs @@ -75,8 +75,11 @@ import GHC.Generics -- -- Computations are functions of a shared environment. -- --- The 'return' function ignores the environment, while @>>=@ passes --- the inherited environment to both subcomputations. +-- The 'return' function ignores the environment, while @m '>>=' k@ +-- passes the inherited environment to both subcomputations: +-- +-- <<images/bind-ReaderT.svg>> +-- type Reader r = ReaderT r Identity -- | Constructor for computations in the reader monad (equivalent to 'asks'). @@ -114,8 +117,11 @@ withReader = withReaderT -- | The reader monad transformer, -- which adds a read-only environment to the given monad. -- --- The 'return' function ignores the environment, while @>>=@ passes --- the inherited environment to both subcomputations. +-- The 'return' function ignores the environment, while @m '>>=' k@ +-- passes the inherited environment to both subcomputations: +-- +-- <<images/bind-ReaderT.svg>> +-- newtype ReaderT r m a = ReaderT { runReaderT :: r -> m a } #if __GLASGOW_HASKELL__ >= 710 deriving (Generic, Generic1) diff --git a/Control/Monad/Trans/Writer/CPS.hs b/Control/Monad/Trans/Writer/CPS.hs index bacab3f0251aa9823276693dd68d0c2e6c03eab4..ca0fb4619cf3701cf762c9c941cfcea2a9644f31 100644 --- a/Control/Monad/Trans/Writer/CPS.hs +++ b/Control/Monad/Trans/Writer/CPS.hs @@ -76,8 +76,12 @@ import GHC.Generics -- --------------------------------------------------------------------------- -- | A writer monad parameterized by the type @w@ of output to accumulate. -- --- The 'return' function produces the output 'mempty', while '>>=' --- combines the outputs of the subcomputations using 'mappend'. +-- The 'return' function produces the output 'mempty', while @m '>>=' k@ +-- combines the outputs of the subcomputations using 'mappend' (also +-- known as @<>@): +-- +-- <<images/bind-WriterT.svg>> +-- type Writer w = WriterT w Identity -- | Construct a writer computation from a (result, output) pair. @@ -116,9 +120,12 @@ mapWriter f = mapWriterT (Identity . f . runIdentity) -- -- * @m@ - The inner monad. -- --- The 'return' function produces the output 'mempty', while '>>=' --- combines the outputs of the subcomputations using 'mappend'. - +-- The 'return' function produces the output 'mempty', while @m '>>=' k@ +-- combines the outputs of the subcomputations using 'mappend' (also +-- known as @<>@): +-- +-- <<images/bind-WriterT.svg>> +-- newtype WriterT w m a = WriterT { unWriterT :: w -> m (a, w) } #if __GLASGOW_HASKELL__ >= 704 deriving (Generic) diff --git a/Control/Monad/Trans/Writer/Lazy.hs b/Control/Monad/Trans/Writer/Lazy.hs index 58a89fffbd95872f925e7d72ad0446cfdd716332..6381f9e5e9ea7c53a601b95c2f4b7bc2cc5cdb8d 100644 --- a/Control/Monad/Trans/Writer/Lazy.hs +++ b/Control/Monad/Trans/Writer/Lazy.hs @@ -81,8 +81,12 @@ import GHC.Generics -- --------------------------------------------------------------------------- -- | A writer monad parameterized by the type @w@ of output to accumulate. -- --- The 'return' function produces the output 'mempty', while @>>=@ --- combines the outputs of the subcomputations using 'mappend'. +-- The 'return' function produces the output 'mempty', while @m '>>=' k@ +-- combines the outputs of the subcomputations using 'mappend' (also +-- known as @<>@): +-- +-- <<images/bind-WriterT.svg>> +-- type Writer w = WriterT w Identity -- | Construct a writer computation from a (result, output) pair. @@ -119,8 +123,12 @@ mapWriter f = mapWriterT (Identity . f . runIdentity) -- -- * @m@ - The inner monad. -- --- The 'return' function produces the output 'mempty', while @>>=@ --- combines the outputs of the subcomputations using 'mappend'. +-- The 'return' function produces the output 'mempty', while @m '>>=' k@ +-- combines the outputs of the subcomputations using 'mappend' (also +-- known as @<>@): +-- +-- <<images/bind-WriterT.svg>> +-- newtype WriterT w m a = WriterT { runWriterT :: m (a, w) } #if __GLASGOW_HASKELL__ >= 704 deriving (Generic) diff --git a/Control/Monad/Trans/Writer/Strict.hs b/Control/Monad/Trans/Writer/Strict.hs index b36d1046581ac98c609a25a649351a3602a3aa11..87a9defd793b8e7b8f8983b0b00ab647dc0c32b7 100644 --- a/Control/Monad/Trans/Writer/Strict.hs +++ b/Control/Monad/Trans/Writer/Strict.hs @@ -84,8 +84,12 @@ import GHC.Generics -- --------------------------------------------------------------------------- -- | A writer monad parameterized by the type @w@ of output to accumulate. -- --- The 'return' function produces the output 'mempty', while @>>=@ --- combines the outputs of the subcomputations using 'mappend'. +-- The 'return' function produces the output 'mempty', while @m '>>=' k@ +-- combines the outputs of the subcomputations using 'mappend' (also +-- known as @<>@): +-- +-- <<images/bind-WriterT.svg>> +-- type Writer w = WriterT w Identity -- | Construct a writer computation from a (result, output) pair. @@ -122,8 +126,12 @@ mapWriter f = mapWriterT (Identity . f . runIdentity) -- -- * @m@ - The inner monad. -- --- The 'return' function produces the output 'mempty', while @>>=@ --- combines the outputs of the subcomputations using 'mappend'. +-- The 'return' function produces the output 'mempty', while @m '>>=' k@ +-- combines the outputs of the subcomputations using 'mappend' (also +-- known as @<>@): +-- +-- <<images/bind-WriterT.svg>> +-- newtype WriterT w m a = WriterT { runWriterT :: m (a, w) } #if __GLASGOW_HASKELL__ >= 704 deriving (Generic)