free-4.6: Monads for free

PortabilityMPTCs, fundeps
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellNone

Control.Monad.Trans.Iter

Contents

Description

Based on Capretta's Iterative Monad Transformer

Unlike Free, this is a true monad transformer.

Synopsis

Documentation

Functions in Haskell are meant to be pure. For example, if an expression has type Int, there should exist a value of the type such that the expression can be replaced by that value in any context without changing the meaning of the program.

Some computations may perform side effects (unsafePerformIO), throw an exception (using error); or not terminate (let infinity = 1 + infinity in infinity).

While the IO monad encapsulates side-effects, and the Either monad encapsulates errors, the Iter monad encapsulates non-termination. The IterT transformer generalizes non-termination to any monadic computation.

The iterative monad transformer

newtype IterT m a Source

The monad supporting iteration based over a base monad m.

 IterT ~ FreeT Identity

Constructors

IterT 

Fields

runIterT :: m (Either a (IterT m a))
 

Instances

MonadTrans IterT 
MonadError e m => MonadError e (IterT m) 
MonadReader e m => MonadReader e (IterT m) 
MonadState s m => MonadState s (IterT m) 
MonadWriter w m => MonadWriter w (IterT m) 
Monad m => MonadFree Identity (IterT m) 
Monad m => Monad (IterT m) 
Monad m => Functor (IterT m) 
Typeable1 m => Typeable1 (IterT m) 
MonadFix m => MonadFix (IterT m) 
MonadPlus m => MonadPlus (IterT m) 
Monad m => Applicative (IterT m) 
Foldable m => Foldable (IterT m) 
(Monad m, Traversable m) => Traversable (IterT m) 
MonadPlus m => Alternative (IterT m) 
MonadIO m => MonadIO (IterT m) 
MonadCont m => MonadCont (IterT m) 
(Monad m, Traversable1 m) => Traversable1 (IterT m) 
Foldable1 m => Foldable1 (IterT m) 
Monad m => Apply (IterT m) 
Monad m => Bind (IterT m) 
Eq (m (Either a (IterT m a))) => Eq (IterT m a) 
(Typeable1 m, Typeable a, Data (m (Either a (IterT m a))), Data a) => Data (IterT m a) 
Ord (m (Either a (IterT m a))) => Ord (IterT m a) 
Read (m (Either a (IterT m a))) => Read (IterT m a) 
Show (m (Either a (IterT m a))) => Show (IterT m a) 
(Monad m, Monoid a) => Monoid (IterT m a) 

Capretta's iterative monad

type Iter = IterT IdentitySource

Plain iterative computations.

iter :: Either a (Iter a) -> Iter aSource

Builds an iterative computation from one first step.

runIter . iter == id

runIter :: Iter a -> Either a (Iter a)Source

Executes the first step of an iterative computation

iter . runIter == id

Combinators

delay :: (Monad f, MonadFree f m) => m a -> m aSource

Adds an extra layer to a free monad value.

In particular, for the iterative monad Iter, this makes the computation require one more step, without changing its final result.

runIter (delay ma) == Right ma

hoistIterT :: Monad n => (forall a. m a -> n a) -> IterT m b -> IterT n bSource

Lift a monad homomorphism from m to n into a Monad homomorphism from IterT m to IterT n.

liftIter :: Monad m => Iter a -> IterT m aSource

Lifts a plain, non-terminating computation into a richer environment. liftIter is a Monad homomorphism.

cutoff :: Monad m => Integer -> IterT m a -> IterT m (Maybe a)Source

Cuts off an iterative computation after a given number of steps. If the number of steps is 0 or less, no computation nor monadic effects will take place.

The step where the final value is produced also counts towards the limit.

Some examples (n ≥ 0):

cutoff 0     _        == return Nothing
cutoff (n+1) . return == return . Just
cutoff (n+1) . lift   ==   lift . liftM Just
cutoff (n+1) . delay  ==  delay . cutoff n
cutoff n     never    == iterate delay (return Nothing) !! n

Calling 'retract . cutoff n' is always terminating, provided each of the steps in the iteration is terminating.

never :: (Monad f, MonadFree f m) => m aSource

A computation that never terminates

interleave :: Monad m => [IterT m a] -> IterT m [a]Source

Interleaves the steps of a finite list of iterative computations, and collects their results.

The resulting computation has as many steps as the longest computation in the list.

interleave_ :: Monad m => [IterT m a] -> IterT m ()Source

Interleaves the steps of a finite list of computations, and discards their results.

The resulting computation has as many steps as the longest computation in the list.

Equivalent to void . interleave.

Consuming iterative monads

retract :: Monad m => IterT m a -> m aSource

retract is the left inverse of lift

 retract . lift = id

fold :: Monad m => (m a -> a) -> IterT m a -> aSource

Tear down a Free Monad using iteration.

foldM :: (Monad m, Monad n) => (m (n a) -> n a) -> IterT m a -> n aSource

Like fold with monadic result.

IterT ~ FreeT Identity

class Monad m => MonadFree f m | m -> f whereSource

Monads provide substitution (fmap) and renormalization (join):

m >>= f = join (fmap f m)

A free Monad is one that does no work during the normalization step beyond simply grafting the two monadic values together.

[] is not a free Monad (in this sense) because join [[a]] smashes the lists flat.

On the other hand, consider:

 data Tree a = Bin (Tree a) (Tree a) | Tip a
 instance Monad Tree where
   return = Tip
   Tip a >>= f = f a
   Bin l r >>= f = Bin (l >>= f) (r >>= f)

This Monad is the free Monad of Pair:

 data Pair a = Pair a a

And we could make an instance of MonadFree for it directly:

 instance MonadFree Pair Tree where
    wrap (Pair l r) = Bin l r

Or we could choose to program with Free Pair instead of Tree and thereby avoid having to define our own Monad instance.

Moreover, Control.Monad.Free.Church provides a MonadFree instance that can improve the asymptotic complexity of code that constructs free monads by effectively reassociating the use of (>>=). You may also want to take a look at the kan-extensions package (http://hackage.haskell.org/package/kan-extensions).

See Free for a more formal definition of the free Monad for a Functor.

Methods

wrap :: f (m a) -> m aSource

Add a layer.

 wrap (fmap f x) ≡ wrap (fmap return x) >>= f

Instances

(Functor f, MonadFree f m) => MonadFree f (ListT m) 
(Functor f, MonadFree f m) => MonadFree f (IdentityT m) 
(Functor f, MonadFree f m) => MonadFree f (MaybeT m) 
Functor f => MonadFree f (Free f) 
Functor f => MonadFree f (F f) 
Monad m => MonadFree Identity (IterT m) 
(Functor f, MonadFree f m, Error e) => MonadFree f (ErrorT e m) 
(Functor f, MonadFree f m, Monoid w) => MonadFree f (WriterT w m) 
(Functor f, MonadFree f m, Monoid w) => MonadFree f (WriterT w m) 
(Functor f, MonadFree f m) => MonadFree f (ContT r m) 
(Functor f, MonadFree f m) => MonadFree f (StateT s m) 
(Functor f, MonadFree f m) => MonadFree f (StateT s m) 
(Functor f, MonadFree f m) => MonadFree f (ReaderT e m) 
(Functor f, Monad m) => MonadFree f (FreeT f m) 
Functor f => MonadFree f (FT f m) 
(Functor f, MonadFree f m, Monoid w) => MonadFree f (RWST r w s m) 
(Functor f, MonadFree f m, Monoid w) => MonadFree f (RWST r w s m) 

Example

This is literate Haskell! To run the example, open the source and copy this comment block into a new file with '.lhs' extension. Compiling to an executable file with the -O2 optimization level is recomended.

For example: ghc -o mandelbrot_iter -O2 MandelbrotIter.lhs ; ./mandelbrot_iter

 {-# LANGUAGE PackageImports #-}
 
 import Control.Arrow
 import Control.Monad.Trans.Iter
 import "mtl" Control.Monad.Reader
 import "mtl" Control.Monad.List
 import "mtl" Control.Monad.Identity
 import Control.Monad.IO.Class
 import Data.Complex
 import Graphics.HGL (runGraphics, Window, withPen,
                      line, RGB (RGB), RedrawMode (Unbuffered, DoubleBuffered), openWindowEx,
                      drawInWindow, mkPen, Style (Solid))

Some fractals can be defined by infinite sequences of complex numbers. For example, to render the Mandelbrot set, the following sequence is generated for each point c in the complex plane:

z₀ = c      
z₁ = z₀² + c     
z₂ = z₁² + c      
…

If, after some iterations, |z_i| ≥ 2, the point is not in the set. We can compute if a point is not in the Mandelbrot set this way:

 escaped :: Complex Double -> Int
 escaped c = loop 0 0 where
   loop z n = if (magnitude z) >= 2 then n
                                    else loop (z*z + c) (n+1)

If c is not in the Mandelbrot set, we get the number of iterations required to prove that fact. But, if c is in the mandelbrot set, escaped will run forever.

We can use the Iter monad to delimit this effect. By applying delay before the recursive call, we decompose the computation into terminating steps.

 escaped :: Complex Double -> Iter Int
 escaped c = loop 0 0 where
   loop z n = if (magnitude z) >= 2 then return n
                                    else delay $ loop (z*z + c) (n+1)

If we draw each point on a canvas after it escapes, we can get a _negative_ image of the Mandelbrot set. Drawing pixels is a side-effect, so it should happen inside the IO monad. Also, we want to have an environment to store the size of the canvas, and the target window.

By using IterT, we can add all these behaviours to our non-terminating computation.

 data Canvas = Canvas { width :: Int, height :: Int, window :: Window }

 type FractalM a = IterT (ReaderT Canvas IO) a

Any simple, non-terminating computation can be lifted into a richer environment.

 escaped' :: Complex Double -> IterT (ReaderT Canvas IO) Int
 escaped' = liftIter . escaped

Then, to draw a point, we can just retrieve the number of iterations until it finishes, and draw it. The color will depend on the number of iterations.

 mandelbrotPoint :: (Int, Int) -> FractalM ()
 mandelbrotPoint p = do
   c <- scale p
   n <- escaped' c
   let color =  if (even n) then RGB   0   0 255 -- Blue
                            else RGB   0   0 127 -- Darker blue
   drawPoint color p

The pixels on the screen don't match the region in the complex plane where the fractal is; we need to map them first. The region we are interested in is Im z = [-1,1], Re z = [-2,1].

 scale :: (Int, Int) -> FractalM (Complex Double)
 scale (xi,yi) = do
   (w,h) <- asks $ (fromIntegral . width) &&& (fromIntegral . height)
   let (x,y) = (fromIntegral xi, fromIntegral yi)
   let im = (-y + h / 2     ) / (h/2)
   let re = ( x - w * 2 / 3 ) / (h/2)
   return $ re :+ im

Drawing a point is equivalent to drawing a line of length one.

 drawPoint :: RGB -> (Int,Int) -> FractalM ()
 drawPoint color p@(x,y) = do
   w <- asks window
   let point = line (x,y) (x+1, y+1)
   liftIO $ drawInWindow w $ mkPen Solid 1 color (flip withPen point)

We may want to draw more than one point. However, if we just sequence the computations monadically, the first point that is not a member of the set will block the whole process. We need advance all the points at the same pace, by interleaving the computations.

 drawMandelbrot :: FractalM ()
 drawMandelbrot = do
   (w,h) <- asks $ width &&& height
   let ps = [mandelbrotPoint (x,y) | x <- [0 .. (w-1)], y <- [0 .. (h-1)]]
   interleave_ ps

To run this computation, we can just use retract, which will run indefinitely:

 runFractalM :: Canvas -> FractalM a -> IO a
 runFractalM canvas  = flip runReaderT canvas . retract

Or, we can trade non-termination for getting an incomplete result, by cutting off after a certain number of steps.

 runFractalM' :: Integer -> Canvas -> FractalM a -> IO (Maybe a)
 runFractalM' n canvas  = flip runReaderT canvas . retract . cutoff n

Thanks to the IterT transformer, we can separate timeout concerns from computational concerns.

 main :: IO ()
 main = do
   let windowWidth = 800
   let windowHeight = 480
   runGraphics $ do
     w <- openWindowEx "Mandelbrot" Nothing (windowWidth, windowHeight) DoubleBuffered (Just 1)
     let canvas = Canvas windowWidth windowHeight w
     runFractalM' 100 canvas drawMandelbrot
     putStrLn $ "Fin"