| 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(- fixh)
- Left shrinking (or Tightening)
- mfix(\x -> a >>= \y -> f x y) = a >>= \y ->- mfix(\x -> f x y)
- Sliding
- mfix(- liftMh . f) =- liftMh (- 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
| MonadFix Complex Source # | Since: base-4.15.0.0 | 
| MonadFix First Source # | Since: base-4.9.0.0 | 
| MonadFix Last Source # | Since: base-4.9.0.0 | 
| MonadFix Max Source # | Since: base-4.9.0.0 | 
| MonadFix Min Source # | Since: base-4.9.0.0 | 
| MonadFix NonEmpty | @since base-4.9.0.0 | 
| MonadFix Identity | @since base-4.8.0.0 | 
| MonadFix First | @since base-4.8.0.0 | 
| MonadFix Last | @since base-4.8.0.0 | 
| MonadFix Down | @since base-4.12.0.0 | 
| MonadFix Dual | @since base-4.8.0.0 | 
| MonadFix Product | @since base-4.8.0.0 | 
| MonadFix Sum | @since base-4.8.0.0 | 
| MonadFix Par1 | @since base-4.9.0.0 | 
| MonadFix IO | @since base-2.01 | 
| MonadFix Maybe | @since base-2.01 | 
| MonadFix Solo | @since base-4.15 | 
| MonadFix [] | @since base-2.01 | 
| Defined in GHC.Internal.Control.Monad.Fix | |
| MonadFix (ST s) | @since base-2.01 | 
| MonadFix (Either e) | @since base-4.3.0.0 | 
| MonadFix (ST s) | @since base-2.01 | 
| MonadFix f => MonadFix (Ap f) | @since base-4.12.0.0 | 
| MonadFix f => MonadFix (Alt f) | @since base-4.8.0.0 | 
| MonadFix f => MonadFix (Rec1 f) | @since base-4.9.0.0 | 
| (MonadFix f, MonadFix g) => MonadFix (Product f g) Source # | Since: base-4.9.0.0 | 
| (MonadFix f, MonadFix g) => MonadFix (f :*: g) | @since base-4.9.0.0 | 
| MonadFix ((->) r) | @since base-2.01 | 
| Defined in GHC.Internal.Control.Monad.Fix | |
| MonadFix f => MonadFix (M1 i c f) | @since base-4.9.0.0 | 
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
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 5120
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)) 5120
Using fix, we can implement versions of repeat as 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]