Copyright | (c) Andy Gill 2001 (c) Oregon Graduate Institute of Science and Technology 2002 |
---|---|
License | BSD-style (see the file libraries/base/LICENSE) |
Maintainer | libraries@haskell.org |
Stability | stable |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
Control.Monad.Fix
Description
Monadic fixpoints.
For a detailed discussion, see Levent Erkok's thesis, Value Recursion in Monadic Computations, Oregon Graduate Institute, 2002.
Documentation
class Monad m => MonadFix (m :: Type -> Type) 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
, for strictmfix
(liftM
h . f) =liftM
h (mfix
(f . h))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
Instances
Instances details
If the function passed to mfix
inspects its argument,
the resulting action will throw a FixIOException
.
Since: ghc-internal-2.17.0.0
Instance details
Defined in GHC.Internal.Control.Monad.Fix
Instance details
Defined in GHC.Internal.Control.Monad.Fix
is the least fixed point of the function fix
ff
,
i.e. the least defined x
such that f x = x
.
When f
is strict, this means that because, by the definition of strictness,
f ⊥ = ⊥
and such the least defined fixed point of any strict function is ⊥
.
Examples
Expand
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
,
Instead of making a recursive call, we introduce a dummy parameter rec
;
when used within fix
, this parameter then refers to fix
’s argument, hence
the recursion is reintroduced.
>>>
fix (\rec n -> if n <= 1 then 1 else n * rec (n-1)) 5
120
Using fix
, we can implement versions of repeat
as
and fix
.
(:)
cycle
as fix
.
(++)
>>>
take 10 $ fix (0:)
[0,0,0,0,0,0,0,0,0,0]
>>>
map (fix (\rec n -> if n < 2 then n else rec (n - 1) + rec (n - 2))) [1..10]
[1,1,2,3,5,8,13,21,34,55]