Skip to content
Snippets Groups Projects

Compare revisions

Changes are shown as if the source revision was being merged into the target revision. Learn more about comparing revisions.

Source

Select target project
No results found

Target

Select target project
No results found
Show changes
Commits on Source (3)
......@@ -27,23 +27,27 @@ module Control.Monad.Signatures (
-- introduced in "Control.Monad.Trans.Cont".
-- Any lifting function @liftCallCC@ should satisfy
--
-- * @'Control.Monad.Trans.Class.lift' (f k) = f' ('Control.Monad.Trans.Class.lift' . k) => 'Control.Monad.Trans.Class.lift' (cf f) = liftCallCC cf f'@
-- @'Control.Monad.Trans.Class.lift' (f k) = f' ('Control.Monad.Trans.Class.lift' . k) => 'Control.Monad.Trans.Class.lift' (cf f) = liftCallCC cf f'@
--
-- This implies that on entry to the continuation any outer monad
-- transformer effect inside @callCC@ will have been rolled back.
type CallCC m a b = ((a -> m b) -> m a) -> m a
-- | Signature of the @catchE@ operation,
-- introduced in "Control.Monad.Trans.Except".
-- Any lifting function @liftCatch@ should satisfy
--
-- * @'Control.Monad.Trans.Class.lift' (cf m f) = liftCatch ('Control.Monad.Trans.Class.lift' . cf) ('Control.Monad.Trans.Class.lift' f)@
-- @'Control.Monad.Trans.Class.lift' (cf m h) = liftCatch cf ('Control.Monad.Trans.Class.lift' m) ('Control.Monad.Trans.Class.lift' . h)@
--
-- This implies that on entry to the handler function any outer monad
-- transformer effect inside @catchE@ will have been rolled back.
type Catch e m a = m a -> (e -> m a) -> m a
-- | Signature of the @listen@ operation,
-- introduced in "Control.Monad.Trans.Writer".
-- Any lifting function @liftListen@ should satisfy
--
-- * @'Control.Monad.Trans.Class.lift' . liftListen = liftListen . 'Control.Monad.Trans.Class.lift'@
-- @'Control.Monad.Trans.Class.lift' . liftListen = liftListen . 'Control.Monad.Trans.Class.lift'@
--
type Listen w m a = m a -> m (a, w)
......@@ -51,6 +55,6 @@ type Listen w m a = m a -> m (a, w)
-- introduced in "Control.Monad.Trans.Writer".
-- Any lifting function @liftPass@ should satisfy
--
-- * @'Control.Monad.Trans.Class.lift' . liftPass = liftPass . 'Control.Monad.Trans.Class.lift'@
-- @'Control.Monad.Trans.Class.lift' . liftPass = liftPass . 'Control.Monad.Trans.Class.lift'@
--
type Pass w m a = m (a, w -> w) -> m a
......@@ -279,6 +279,9 @@ liftCallCC' callCC f = AccumT $ \ s ->
{-# INLINE liftCallCC' #-}
-- | Lift a @catchE@ operation to the new monad.
-- The uniformity property (see "Control.Monad.Signatures") implies that
-- the lifted @catchE@ discards any output from the body on entering
-- the handler.
liftCatch :: Catch e m (a, w) -> Catch e (AccumT w m) a
liftCatch catchE m h =
AccumT $ \ w -> runAccumT m w `catchE` \ e -> runAccumT (h e) w
......
......@@ -16,7 +16,8 @@
-- Stability : experimental
-- Portability : portable
--
-- This monad transformer extends a monad with the ability to throw exceptions.
-- This monad transformer extends a monad with the ability to throw
-- and catch exceptions.
--
-- A sequence of actions terminates normally, producing a value,
-- only if none of the actions in the sequence throws an exception.
......@@ -80,7 +81,9 @@ import GHC.Generics
-- | The parameterizable exception monad.
--
-- Computations are either exceptions or normal values.
-- Computations are either exceptions (of any type) or normal values.
-- These computations are plain values, and are unrelated to the
-- "Control.Exception" mechanism, which is tied to the 'IO' monad.
--
-- The 'return' function returns a normal value, while @>>=@ exits on
-- the first exception. For a variant that continues after an error
......@@ -118,10 +121,13 @@ withExcept = withExceptT
--
-- @ExceptT@ constructs a monad parameterized over two things:
--
-- * e - The exception type.
-- * e - An arbitrary exception type.
--
-- * m - The inner monad.
--
-- The monadic computations are a plain values. They are unrelated to
-- the "Control.Exception" mechanism, which is tied to the 'IO' monad.
--
-- The 'return' function yields a computation that produces the given
-- value, while @>>=@ sequences two subcomputations, exiting on the
-- first exception.
......
......@@ -409,6 +409,9 @@ liftCallCC' callCC f = RWST $ \ r s w ->
{-# INLINE liftCallCC' #-}
-- | Lift a @catchE@ operation to the new monad.
-- The uniformity property (see "Control.Monad.Signatures") implies that
-- the lifted @catchE@ discards any output or changes to the state from
-- the body on entering the handler.
liftCatch :: Catch e m (a,s,w) -> Catch e (RWST r w s m) a
liftCatch catchE m h =
RWST $ \ r s w -> unRWST m r s w `catchE` \ e -> unRWST (h e) r s w
......
......@@ -393,6 +393,9 @@ liftCallCC' callCC f = RWST $ \ r s ->
{-# INLINE liftCallCC' #-}
-- | Lift a @catchE@ operation to the new monad.
-- The uniformity property (see "Control.Monad.Signatures") implies that
-- the lifted @catchE@ discards any output or changes to the state from
-- the body on entering the handler.
liftCatch :: Catch e m (a,s,w) -> Catch e (RWST r w s m) a
liftCatch catchE m h =
RWST $ \ r s -> runRWST m r s `catchE` \ e -> runRWST (h e) r s
......
......@@ -397,6 +397,9 @@ liftCallCC' callCC f = RWST $ \ r s ->
{-# INLINE liftCallCC' #-}
-- | Lift a @catchE@ operation to the new monad.
-- The uniformity property (see "Control.Monad.Signatures") implies that
-- the lifted @catchE@ discards any output or changes to the state from
-- the body on entering the handler.
liftCatch :: Catch e m (a,s,w) -> Catch e (RWST r w s m) a
liftCatch catchE m h =
RWST $ \ r s -> runRWST m r s `catchE` \ e -> runRWST (h e) r s
......
......@@ -336,6 +336,9 @@ liftCallCC' callCC f = StateT $ \ s ->
{-# INLINE liftCallCC' #-}
-- | Lift a @catchE@ operation to the new monad.
-- The uniformity property (see "Control.Monad.Signatures") implies
-- that the lifted @catchE@ rolls back to the original state on entering
-- the handler.
liftCatch :: Catch e m (a,s) -> Catch e (StateT s m) a
liftCatch catchE m h =
StateT $ \ s -> runStateT m s `catchE` \ e -> runStateT (h e) s
......
......@@ -337,6 +337,9 @@ liftCallCC' callCC f = StateT $ \ s ->
{-# INLINE liftCallCC' #-}
-- | Lift a @catchE@ operation to the new monad.
-- The uniformity property (see "Control.Monad.Signatures") implies
-- that the lifted @catchE@ rolls back to the original state on entering
-- the handler.
liftCatch :: Catch e m (a,s) -> Catch e (StateT s m) a
liftCatch catchE m h =
StateT $ \ s -> runStateT m s `catchE` \ e -> runStateT (h e) s
......
......@@ -283,14 +283,18 @@ censor f m = WriterT $ \ w -> do
{-# INLINE censor #-}
-- | Uniform lifting of a @callCC@ operation to the new monad.
-- This version rolls back to the original state on entering the
-- continuation.
-- The uniformity property (see "Control.Monad.Signatures") implies that
-- the lifted @callCC@ discards any output from the body on entering
-- the saved continuation.
liftCallCC :: CallCC m (a, w) (b, w) -> CallCC (WriterT w m) a b
liftCallCC callCC f = WriterT $ \ w ->
callCC $ \ c -> unWriterT (f (\ a -> WriterT $ \ _ -> c (a, w))) w
{-# INLINE liftCallCC #-}
-- | Lift a @catchE@ operation to the new monad.
-- The uniformity property (see "Control.Monad.Signatures") implies that
-- the lifted @catchE@ discards any output from the body on entering
-- the handler.
liftCatch :: Catch e m (a, w) -> Catch e (WriterT w m) a
liftCatch catchE m h = WriterT $ \ w ->
unWriterT m w `catchE` \ e -> unWriterT (h e) w
......
......@@ -317,6 +317,9 @@ censor f m = WriterT $ do
{-# INLINE censor #-}
-- | Lift a @callCC@ operation to the new monad.
-- The uniformity property (see "Control.Monad.Signatures") implies that
-- the lifted @callCC@ discards any output from the body on entering
-- the saved condinuation.
liftCallCC :: (Monoid w) => CallCC m (a,w) (b,w) -> CallCC (WriterT w m) a b
liftCallCC callCC f = WriterT $
callCC $ \ c ->
......@@ -324,6 +327,9 @@ liftCallCC callCC f = WriterT $
{-# INLINE liftCallCC #-}
-- | Lift a @catchE@ operation to the new monad.
-- The uniformity property (see "Control.Monad.Signatures") implies that
-- the lifted @catchE@ discards any output from the body on entering
-- the handler.
liftCatch :: Catch e m (a,w) -> Catch e (WriterT w m) a
liftCatch catchE m h =
WriterT $ runWriterT m `catchE` \ e -> runWriterT (h e)
......
......@@ -320,6 +320,9 @@ censor f m = WriterT $ do
{-# INLINE censor #-}
-- | Lift a @callCC@ operation to the new monad.
-- The uniformity property (see "Control.Monad.Signatures") implies that
-- the lifted @callCC@ discards any output from the body on entering
-- the saved continuation.
liftCallCC :: (Monoid w) => CallCC m (a,w) (b,w) -> CallCC (WriterT w m) a b
liftCallCC callCC f = WriterT $
callCC $ \ c ->
......@@ -327,6 +330,9 @@ liftCallCC callCC f = WriterT $
{-# INLINE liftCallCC #-}
-- | Lift a @catchE@ operation to the new monad.
-- The uniformity property (see "Control.Monad.Signatures") implies that
-- the lifted @catchE@ discards any output from the body on entering
-- the handler.
liftCatch :: Catch e m (a,w) -> Catch e (WriterT w m) a
liftCatch catchE m h =
WriterT $ runWriterT m `catchE` \ e -> runWriterT (h e)
......
<?xml version="1.0" encoding="UTF-8" standalone="no"?>
<!DOCTYPE svg PUBLIC "-//W3C//DTD SVG 1.1//EN"
"http://www.w3.org/Graphics/SVG/1.1/DTD/svg11.dtd">
<svg width="390" height="180"
xmlns="http://www.w3.org/2000/svg" xmlns:xlink="http://www.w3.org/1999/xlink">
<defs>
<marker id="arrow" viewBox="0 0 10 10" refX="5" refY="5"
markerWidth="5" markerHeight="5"
orient="auto-start-reverse">
<path d="M 0 0 L 10 5 L 0 10 z" />
</marker>
<marker id="extra-arrow" viewBox="0 0 10 10" refX="5" refY="5"
markerWidth="5" markerHeight="5"
orient="auto-start-reverse">
<path fill="#44f" d="M 0 0 L 10 5 L 0 10 z" />
</marker>
<style type="text/css">
line.arrow {
fill: none; stroke: black; stroke-width: 4;
marker-end: url(#arrow);
}
circle.action {
fill: #f8ddbb; stroke: black; stroke-width: 4;
}
text.action {
fill: black; stroke: none;
font-family: sans-serif; font-size: 35px;
dominant-baseline: central; text-anchor: middle;
}
.extra {
fill: none; stroke: #44f; stroke-width: 3;
marker-end: url(#extra-arrow);
}
circle.mappend {
fill: none; stroke: #44f; stroke-width: 3;
}
text.mappend {
fill: #44f; stroke: none;
font-family: sans-serif; font-size: 26px;
dominant-baseline: central; text-anchor: middle;
}
</style>
</defs>
<g transform="scale(0.6) translate(50,50)">
<path class="extra" d="M 0,0 L 80,0 A 20 20 0 0 1 100,20 L 100,52"/>
<path class="extra" d="M 80,0 L 225,0"/>
<circle class="mappend" cx="250" cy="0" r="20"/>
<text class="mappend" x="250" y="0">&lt;&gt;</text>
<path class="extra" d="M 270,0 L 380,0 A 20 20 0 0 1 400,20 L 400,52"/>
<path class="extra" d="M 230,200 A 20 20 0 0 0 250,180 L 250,27"/>
<path class="extra" d="M 100,140 L 100,180 A 20 20 0 0 0 120,200 L 373,200"/>
<circle class="mappend" cx="400" cy="200" r="20"/>
<text class="mappend" x="400" y="200">&lt;&gt;</text>
<path class="extra" d="M 400,140 L 400,173"/>
<path class="extra" d="M 420,200 L 550,200"/>
<text class="mappend" x="15" y="-20">w</text>
<line class="arrow" x1="140" y1="100" x2="350" y2="100"/>
<line class="arrow" x1="440" y1="100" x2="550" y2="100"/>
<circle class="action" cx="100" cy="100" r="40"/>
<text class="action" x="100" y="100">m</text>
<circle class="action" cx="400" cy="100" r="40"/>
<text class="action" x="400" y="100">k</text>
</g>
</svg>
<?xml version="1.0" encoding="UTF-8" standalone="no"?>
<!DOCTYPE svg PUBLIC "-//W3C//DTD SVG 1.1//EN"
"http://www.w3.org/Graphics/SVG/1.1/DTD/svg11.dtd">
<svg width="390" height="150"
xmlns="http://www.w3.org/2000/svg" xmlns:xlink="http://www.w3.org/1999/xlink">
<defs>
<marker id="arrow" viewBox="0 0 10 10" refX="5" refY="5"
markerWidth="5" markerHeight="5"
orient="auto-start-reverse">
<path d="M 0 0 L 10 5 L 0 10 z" />
</marker>
<marker id="extra-arrow" viewBox="0 0 10 10" refX="5" refY="5"
markerWidth="5" markerHeight="5"
orient="auto-start-reverse">
<path fill="#44f" d="M 0 0 L 10 5 L 0 10 z" />
</marker>
<style type="text/css">
line.arrow {
fill: none; stroke: black; stroke-width: 4;
marker-end: url(#arrow);
}
circle.action {
fill: #f8ddbb; stroke: black; stroke-width: 4;
}
text.action {
fill: black; stroke: none;
font-family: sans-serif; font-size: 35px;
dominant-baseline: central; text-anchor: middle;
}
.extra {
fill: none; stroke: #44f; stroke-width: 3;
marker-end: url(#extra-arrow);
}
circle.mappend {
fill: none; stroke: #44f; stroke-width: 3;
}
text.mappend {
fill: #44f; stroke: none;
font-family: sans-serif; font-size: 26px;
dominant-baseline: central; text-anchor: middle;
}
</style>
</defs>
<g transform="scale(0.6) translate(50,50)">
<path class="extra" d="M 0,0 L 80,0 A 20 20 0 0 1 100,20 L 100,52"/>
<path class="extra" d="M 80,0 L 380,0 A 20 20 0 0 1 400,20 L 400,52"/>
<text class="mappend" x="15" y="-20">r</text>
<line class="arrow" x1="140" y1="100" x2="350" y2="100"/>
<line class="arrow" x1="440" y1="100" x2="550" y2="100"/>
<circle class="action" cx="100" cy="100" r="40"/>
<text class="action" x="100" y="100">m</text>
<circle class="action" cx="400" cy="100" r="40"/>
<text class="action" x="400" y="100">k</text>
</g>
</svg>
<?xml version="1.0" encoding="UTF-8" standalone="no"?>
<!DOCTYPE svg PUBLIC "-//W3C//DTD SVG 1.1//EN"
"http://www.w3.org/Graphics/SVG/1.1/DTD/svg11.dtd">
<svg width="360" height="150"
xmlns="http://www.w3.org/2000/svg" xmlns:xlink="http://www.w3.org/1999/xlink">
<defs>
<marker id="arrow" viewBox="0 0 10 10" refX="5" refY="5"
markerWidth="5" markerHeight="5"
orient="auto-start-reverse">
<path d="M 0 0 L 10 5 L 0 10 z" />
</marker>
<marker id="extra-arrow" viewBox="0 0 10 10" refX="5" refY="5"
markerWidth="5" markerHeight="5"
orient="auto-start-reverse">
<path fill="#44f" d="M 0 0 L 10 5 L 0 10 z" />
</marker>
<style type="text/css">
line.arrow {
fill: none; stroke: black; stroke-width: 4;
marker-end: url(#arrow);
}
circle.action {
fill: #f8ddbb; stroke: black; stroke-width: 4;
}
text.action {
fill: black; stroke: none;
font-family: sans-serif; font-size: 35px;
dominant-baseline: central; text-anchor: middle;
}
.extra {
fill: none; stroke: #44f; stroke-width: 3;
marker-end: url(#extra-arrow);
}
circle.mappend {
fill: none; stroke: #44f; stroke-width: 3;
}
text.mappend {
fill: #44f; stroke: none;
font-family: sans-serif; font-size: 26px;
dominant-baseline: central; text-anchor: middle;
}
</style>
</defs>
<g transform="scale(0.6)">
<path class="extra" d="M 100,140 L 100,180 A 20 20 0 0 0 120,200 L 373,200"/>
<circle class="mappend" cx="400" cy="200" r="20"/>
<text class="mappend" x="400" y="200">&lt;&gt;</text>
<path class="extra" d="M 400,140 L 400,173"/>
<path class="extra" d="M 420,200 L 550,200"/>
<text class="mappend" x="520" y="180">w</text>
<line class="arrow" x1="140" y1="100" x2="350" y2="100"/>
<line class="arrow" x1="440" y1="100" x2="550" y2="100"/>
<circle class="action" cx="100" cy="100" r="40"/>
<text class="action" x="100" y="100">m</text>
<circle class="action" cx="400" cy="100" r="40"/>
<text class="action" x="400" y="100">k</text>
</g>
</svg>