{-# LANGUAGE Trustworthy #-}
------------------------------------------------------------------------------- |-- Module : Control.Monad.Fix-- 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 : experimental-- Portability : portable---- Monadic fixpoints.---- For a detailed discussion, see Levent Erkok's thesis,-- /Value Recursion in Monadic Computations/, Oregon Graduate Institute, 2002.-------------------------------------------------------------------------------
module Control.Monad.Fix (
MonadFix(mfix),
fix
) where
import Prelude
import System.IO
import Data.Function (fix)
import GHC.ST-- | 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' ('Control.Monad.liftM' h . f) = 'Control.Monad.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.
class (Monad m) =>MonadFixm where
-- | 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.mfix :: (a -> ma) -> ma-- Instances of MonadFix for Prelude monads
instance MonadFixMaybe where
mfixf = let a = f (unJusta) in a
where unJust (Justx) = xunJustNothing = error"mfix Maybe: Nothing"
instance MonadFix[] where
mfixf = case fix (f.head) of
[] -> []
(x:_) -> x:mfix (tail.f)
instance MonadFixIO where
mfix = fixIO
instance MonadFix ((->)r) where
mfixf = \ r -> let a = far in a
instance MonadFix (Eithere) where
mfixf = let a = f (unRighta) in a
where unRight (Rightx) = xunRight (Left _) = error"mfix Either: Left"
instance MonadFix (STs) where
mfix = fixST