[Haskell-cafe] Re: Re: Monads from Functors

Jonathan Cast jonathanccast at fastmail.fm
Wed Apr 8 19:37:23 EDT 2009


On Thu, 2009-04-09 at 01:24 +0200, Ben Franksen wrote:
> BTW, is this (ContT t) somehow related to the 'free monad' over t?

The free monad over t is just

  data FreeMonad t a
    = Return a
    | JoinLift (t (FreeMonad t a))
  instance Functor t => Monad (FreeMonad t) where
    return = Return
    Return x >>= f = f x
    JoinLift a >>= f = JoinLift ((>>= f) <$> a)
  lift :: Functor t => t a -> FreeMonad t a
  lift a = JoinLift (return <$> a)

So they're obviously different.  Here's what free monads are for:
picking a functor f so that FreeMonad f becomes a randomly chosen
monad :), we could define

  data IOStmt a
    = GetChar (Char -> a)
    | PutChar Char a
  instance Functor IOStmt where
    fmap f (GetChar g) = GetChar (f . g)
    fmap f (PutChar ch x) = PutChar ch (f x)
  getCharStmt :: IOStmt Char
  getCharStmt = GetChar id
  putCharStmt :: Char -> IOStmt ()
  putCharStmt ch = PutChar ch ()

  type IO = FreeMonad IOStmt
  getChar :: IO Char
  getChar = lift getCharStmt
  putChar :: Char -> IO ()
  putChar = lift . putCharStmt

jcc




More information about the Haskell-Cafe mailing list