Haskell Hierarchical Libraries (base package)ContentsIndex
Control.Monad.Fix
Portability portable
Stability experimental
Maintainer libraries@haskell.org
Description

Monadic fixpoints.

For a detailed discussion, see Levent Erkok's thesis, Value Recursion in Monadic Computations, Oregon Graduate Institute, 2002.

Synopsis
class Monad m => MonadFix m where
mfix :: (a -> m a) -> m a
fix :: (a -> a) -> a
Documentation
class Monad m => MonadFix m where

Monads having fixed points with a 'knot-tying' semantics. Instances of MonadFix should satisfy the following laws:

purity
mfix (return . h) = return (fix h)
left shrinking (or tightening)
mfix (\x -> a >>= \y -> f x y) = \y -> mfix (\x -> f x y)
sliding
mfix (liftM h . f) = liftM h (mfix (f . h)), for strict h.
nesting
mfix (\x -> mfix (\y -> f x y)) = mfix (\x -> f x x)

This class is used in the translation of the recursive do notation supported by GHC and Hugs.

Methods
mfix :: (a -> m a) -> m a
The fixed point of a monadic computation. mfix f executes the action f only once, with the eventual output fed back as the input. Hence f should not be strict, for then mfix f would diverge.
Instances
Error e => MonadFix (Either e)
(MonadFix m, Error e) => MonadFix (ErrorT e m)
MonadFix Maybe
MonadFix []
MonadFix IO
MonadFix Identity
Monoid w => MonadFix (RWS r w s)
(Monoid w, MonadFix m) => MonadFix (RWST r w s m)
MonadFix ((->) r)
MonadFix (Reader r)
MonadFix m => MonadFix (ReaderT r m)
MonadFix (ST s)
MonadFix (ST s)
MonadFix (State s)
MonadFix m => MonadFix (StateT s m)
Monoid w => MonadFix (Writer w)
(Monoid w, MonadFix m) => MonadFix (WriterT w m)
fix :: (a -> a) -> a
fix f is the least fixed point of the function f, i.e. the least defined x such that f x = x.
Produced by Haddock version 0.6