base-4.12.0.0: Basic libraries

Copyright(c) Andy Gill 2001
(c) Oregon Graduate Institute of Science and Technology 2002
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainerlibraries@haskell.org
Stabilityexperimental
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

Control.Monad.Fix

Description

Monadic fixpoints.

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

Synopsis

Documentation

class Monad m => MonadFix m where Source #

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) = a >>= \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 Source #

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
MonadFix [] #

Since: base-2.1

Instance details

Defined in Control.Monad.Fix

Methods

mfix :: (a -> [a]) -> [a] Source #

MonadFix Maybe #

Since: base-2.1

Instance details

Defined in Control.Monad.Fix

Methods

mfix :: (a -> Maybe a) -> Maybe a Source #

MonadFix IO #

Since: base-2.1

Instance details

Defined in Control.Monad.Fix

Methods

mfix :: (a -> IO a) -> IO a Source #

MonadFix Par1 #

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.Fix

Methods

mfix :: (a -> Par1 a) -> Par1 a Source #

MonadFix NonEmpty #

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.Fix

Methods

mfix :: (a -> NonEmpty a) -> NonEmpty a Source #

MonadFix Down #

Since: base-4.12.0.0

Instance details

Defined in Control.Monad.Fix

Methods

mfix :: (a -> Down a) -> Down a Source #

MonadFix Product #

Since: base-4.8.0.0

Instance details

Defined in Control.Monad.Fix

Methods

mfix :: (a -> Product a) -> Product a Source #

MonadFix Sum #

Since: base-4.8.0.0

Instance details

Defined in Control.Monad.Fix

Methods

mfix :: (a -> Sum a) -> Sum a Source #

MonadFix Dual #

Since: base-4.8.0.0

Instance details

Defined in Control.Monad.Fix

Methods

mfix :: (a -> Dual a) -> Dual a Source #

MonadFix Last #

Since: base-4.8.0.0

Instance details

Defined in Control.Monad.Fix

Methods

mfix :: (a -> Last a) -> Last a Source #

MonadFix First #

Since: base-4.8.0.0

Instance details

Defined in Control.Monad.Fix

Methods

mfix :: (a -> First a) -> First a Source #

MonadFix Identity #

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Methods

mfix :: (a -> Identity a) -> Identity a Source #

MonadFix Option #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

mfix :: (a -> Option a) -> Option a Source #

MonadFix Last #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

mfix :: (a -> Last a) -> Last a Source #

MonadFix First #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

mfix :: (a -> First a) -> First a Source #

MonadFix Max #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

mfix :: (a -> Max a) -> Max a Source #

MonadFix Min #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

mfix :: (a -> Min a) -> Min a Source #

MonadFix (Either e) #

Since: base-4.3.0.0

Instance details

Defined in Control.Monad.Fix

Methods

mfix :: (a -> Either e a) -> Either e a Source #

MonadFix (ST s) #

Since: base-2.1

Instance details

Defined in Control.Monad.Fix

Methods

mfix :: (a -> ST s a) -> ST s a Source #

MonadFix (ST s) #

Since: base-2.1

Instance details

Defined in Control.Monad.ST.Lazy.Imp

Methods

mfix :: (a -> ST s a) -> ST s a Source #

MonadFix f => MonadFix (Rec1 f) #

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.Fix

Methods

mfix :: (a -> Rec1 f a) -> Rec1 f a Source #

MonadFix f => MonadFix (Alt f) #

Since: base-4.8.0.0

Instance details

Defined in Control.Monad.Fix

Methods

mfix :: (a -> Alt f a) -> Alt f a Source #

MonadFix f => MonadFix (Ap f) #

Since: base-4.12.0.0

Instance details

Defined in Control.Monad.Fix

Methods

mfix :: (a -> Ap f a) -> Ap f a Source #

MonadFix ((->) r :: Type -> Type) #

Since: base-2.1

Instance details

Defined in Control.Monad.Fix

Methods

mfix :: (a -> r -> a) -> r -> a Source #

(MonadFix f, MonadFix g) => MonadFix (f :*: g) #

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.Fix

Methods

mfix :: (a -> (f :*: g) a) -> (f :*: g) a Source #

(MonadFix f, MonadFix g) => MonadFix (Product f g) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

mfix :: (a -> Product f g a) -> Product f g a Source #

MonadFix f => MonadFix (M1 i c f) #

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.Fix

Methods

mfix :: (a -> M1 i c f a) -> M1 i c f a Source #

fix :: (a -> a) -> a Source #

fix f is the least fixed point of the function f, i.e. the least defined x such that f x = x.

For example, we can write the factorial function using direct recursion as

>>> let fac n = if n <= 1 then 1 else n * fac (n-1) in fac 5
120

This uses the fact that Haskell’s let introduces recursive bindings. We can rewrite this definition using fix,

>>> fix (\rec n -> if n <= 1 then 1 else n * rec (n-1)) 5
120

Instead of making a recursive call, we introduce a dummy parameter rec; when used within fix, this parameter then refers to fix' argument, hence the recursion is reintroduced.