Monad composition

Theodore Norvell theo@engr.mun.ca
Thu, 24 Jan 2002 11:49:23 -0800


Tom Bevan wrote:
> 
> Hi all,
> 
> I'm writing a programme which requires IO actions to be interleaved with
> operations on a State monad. From what I can work out, this means that
> the IO Monad and the StateTransformation monad need to be composed into
> a single highr order monad.
> Does anyone have any references or pointers on how this should be done?

I'd also be interested in references or pointers.  While, the
logic isn't hard to get right, it is easy to make do-it-yourself
state monads lazier than you intended.

Below is how I've done it in one project.  I'd be interested in any 
comments from others on this code.  I had two other requirements
beyond what you mention. I wanted to be able to stop the computation
in the middle (in case an error was detected, for example). Hence the
use of the Ok_Err type.  Also, I wanted to make sure that each state
is evaluated before moving on to the next step of the computation;
this explains the ubiquitous use of "seq". You also have to
make sure that the constructors for the state are strict and generally
be careful that after you've computed a new state the last state is garbage.

BTW the "Ex" in "StateExTrans" stands for "exception", but this monad
doesn't support exception handling yet, so this is a misnomer.

Cheers,
Theodore Norvell

----------------------------
Dr. Theodore Norvell                                           theo@engr.mun.ca
Electrical and Computer Engineering                http://www.engr.mun.ca/~theo
Engineering and Applied Science
Memorial University of Newfoundland
St. John's, NF, Canada, A1B 3X5

Currently visiting the Department of Computer Science and ICICS at the
University of British Columbia. See my webpage for contact details.

---------Here is the monad-------------

module StateExMonad( Ok_Err(..),
                     StateExTrans(),
                     runSET,
                     stop,
                     for,
                     getState,
                     putState,
                     command,
                     expression,
                     doIO )
where

        data Ok_Err s a = Ok s a | Err
        data StateExTrans s a = SET (s -> IO (Ok_Err s a))
        
        instance Functor  (StateExTrans s) where
        	--fmap :: (a -> b) -> (StateExTrans s a -> StateExTrans s b)
        	fmap f x = do a <- x
        		      return (f a)
        	                                       
        instance Monad (StateExTrans s) where
        	-- return :: a -> StateExTrans s a
        	return a = SET (\ s -> seq s (return (Ok s a)))
        	-- >>= :: (StateExTrans s a) -> (a -> StateExTrans s b) ->
        	--		(StateExTrans s b)
        	(SET st) >>= f
        		= SET(\ s ->
        		      seq s (do ok_err' <- st s
        			        case ok_err' of
        			          (Ok s' a) ->
        				   let (SET st') = f a
        				   in st' s'
        			          Err ->  return Err))
                
        runSET :: StateExTrans s a -> s -> (IO (Ok_Err s a))
        runSET (SET f) s = f s
        
        stop :: StateExTrans s a
        stop = SET(\s -> return Err)
        
        for :: (Functor m, Monad m) => [i] -> (i -> m a) -> m [a]
        for [] p = return []
        for (i:rest) p = p i >>= (\a -> fmap (a:) (for rest p))
        
        getState = SET (\s -> seq s (return (Ok s s)))
        
        putState s = SET (\_ -> seq s (return (Ok s ())))
        
        command :: (s -> s) -> StateExTrans s ()
        command c = SET(\s -> seq s (return (Ok (c s) ())))
        
        expression :: (s -> a) -> StateExTrans s a
        expression e = SET(\s -> seq s (return (Ok s (e s))))
        
        doIO :: (IO a) -> StateExTrans s a
        doIO io' = SET(\s -> seq s (io' >>= (\a -> return (Ok s a)))