[Haskell-beginners] Is there a simpler way? Building a monad on `IO' Monad
Daniel Fischer
daniel.is.fischer at googlemail.com
Sun Jan 9 12:27:51 CET 2011
On Sunday 09 January 2011 11:47:40, Arlen Cuss wrote:
> Hi all,
>
> Thanks for previous help on this list! I really appreciate it.
>
> Today I wrote a monad and I'm not sure if I took a complicated way about
> it. It's essentially a State monad, except with some specialised
> functions that operate on the `state' if you will (though the state is
> rarely mutated)—you initialise it with two Handles (e.g. stdin, stdout),
> and then a set of specialised functions defined `within' the monad will
> operate on those handles. It saves you from passing the Handles
> throughout the functions and subcalls.
>
> It's quite possible there already exists a monad for this job, or that
> IO will actually let you do this, but I didn't find it in a bit of
> searching, and concluded this would be a fun way to solve the problem.
> If anyone has any advice on shortening the code, or possibly removing
> the need for it, please let me know!
>
> Here's the main monad:
> > import System.IO
> > import Control.Applicative
> >
> > newtype IODirector a = IODirector { runIODirector :: (Handle,Handle)
>
> -> IO (a, (Handle,Handle)) }
Enter Monad transformers (you're not the first to discover them, congrats
nevertheless :).
You can make it a type synonym
type IODirector = StateT (Handle,Handle) IO
or make it a newtype, where you can let GHC derive all interesting stuff:
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
import Control.Monad.State[.Strict]
newtype IODirector a
= IODirector { director :: StateT (Handle,Handle) IO a }
deriving (Functor, Monad, MonadPlus, MonadState (Handle,Handle),
MonadIO)
runIODirector = runStateT . director
>
> > instance Monad IODirector where
> > return a = IODirector $ \hs -> return (a, hs)
> > m >>= k = IODirector $ \hs -> do (a, hs) <- runIODirector m hs
> > runIODirector (k a) hs
>
> This is basically the same as State, except we `return' to the IO monad,
> as is the result of the stateful computation an I/O action, IO (a,
> (Handle,Handle)).
>
> We then have a type-class for the actual I/O we can perform within the
>
> monad:
> > class MonadDirectedIO a where
> > dPutStr :: String -> a ()
> > dPutStrLn :: String -> a ()
> >
> > dGetLine :: a String
> > dGetChar :: a Char
>
> ...
>
> The functions here continue for all the ones from IO I really wanted to
>
> use, and the instance is not surprising:
> > instance MonadDirectedIO IODirector where
> > dPutStr s = IODirector $ \hs@(_,hOut) -> do hPutStr hOut s
> > return ((), hs)
> > dPutStrLn = dPutStr . (++ "\n")
> >
> > dGetLine = IODirector $ \hs@(hIn,_) -> do r <- hGetLine hIn
> > return (r, hs)
> > dGetChar = IODirector $ \hs@(hIn,_) -> do r <- hGetChar hIn
> > return (r, hs)
>
> I'm aware I didn't have to put this in a type-class, but it seemed a
> reasonable thing to do.
>
> There was a little plumbing work to `enclose' IO within this monad. My
> question is - did I do it right? Or is there a simpler way?
There is a simpler way, with MonadState (Handle,Handle) (btw., perhaps it's
better to use a self-defined record than to use a pair, if you access the
fields by name you can't confuse the positions of in and out) and MonadIO:
outIO :: (Handle -> a -> IO b) -> a -> IODirector b
outIO action value = do
hOut <- gets snd -- gets outHandle
liftIO $ action hOut value
inIO :: (Handle -> IO a) -> IODirector a
inIO action = do
hIn <- gets fst -- gets inHandle
liftIO $ action hIn
>
> Of course, if there's already such functionality in the built-in, I'd
> also be interested to hear ... ;-)
Mostly yes (you have to fill in a particular details of course), the Monad
transformers provided by the libraries (mtl, transformers, others; I
recommend using mtl [now a wrwpper around transformers] or transformers)
have most of the functionality you need.
As you've seen, combining Monads is quite useful. Fortunately, there have
been clever people who have found that out before, so you need not
implement everything yourself.
>
> Cheers!
>
> Arlen
Cheers,
Daniel
More information about the Beginners
mailing list