order of monad transformers

How does one consider the best ordering of monad transformers? For example, if I'm combining ErrorT, StateT (or State), and WriterT (or Writer)? But not just this specific example---what principles can one consult to determine ordering? Thanks, Mike

{-# LANGUAGE GeneralizedNewtypeDeriving #-}
Hello Mike If the is a principal as such, I'd suggest that's working out the return type that you want your run function to have. Or more plainly - work out what you want the result to be. Thats a bit gnomic of course, so here are two examples with ErrorT (for failure) and WriterT (for logging), the ErrMsg type is contrived slightly to be a distinct type. This message should be literate Haskell if my mail service likes me:
module Transforming where
import Control.Monad.Error import Control.Monad.Identity import Control.Monad.Writer
type Log = String newtype ErrMsg = ErrMsg { getMsg :: String } deriving Show
newtype EWI a = EWI { getEWI :: ErrorT ErrMsg (WriterT Log Identity) a } deriving (Functor, Monad, MonadWriter Log, MonadError ErrMsg)
The run functions are pretty /natural/ just the run functions of the monad transformer stack in the reverse order. Note the /outer tupling/ over the Either type in the run function - runEWI always returns a log regardless of whether the computation fails with an error... [ without embellishments: (Either _ _,_) ]
runEWI :: EWI a -> (Either ErrMsg a, Log) runEWI ma = runIdentity (runWriterT (runErrorT (getEWI ma)))
newtype WEI a = WEI { getWEI :: WriterT Log (ErrorT ErrMsg Identity) a } deriving (Functor, Monad, MonadWriter Log, MonadError ErrMsg)
Note the Either type has an inner tuple in the run function - runWEI returns a log /only/ when the computation succeeds otherwise it fails with just an error... [ without embellishments: Either _ (_,_) ]
runWEI :: WEI a -> Either ErrMsg (a, Log) runWEI ma = runIdentity (runErrorT (runWriterT (getWEI ma)))
Support code
instance Error ErrMsg where noMsg = ErrMsg "" strMsg = ErrMsg

Apologies - the paragraph of the last message was riddled with typos, it should read: If there is a principal as such, I'd suggest that it's working out the return type you want your run function to have. Or more plainly - work out what you want the result to be.
If the is a principal as such, I'd suggest that's working out the return type that you want your run function to have. Or more plainly - work out what you want the result to be.
Best wishes Stephen

Thanks Stephen and Brent! I will try working out the examples you gave. I don't immediate comprehend Brent's explanation, but I think I will need to actually code and run some examples and then I'll probably get it. Thanks, Mike

On Tue, Nov 03, 2009 at 06:29:46PM -0800, Michael Mossey wrote:
How does one consider the best ordering of monad transformers? For example, if I'm combining ErrorT, StateT (or State), and WriterT (or Writer)? But not just this specific example---what principles can one consult to determine ordering?
As Stephen has illustrated, the principle is that the effects of _inner_ transformers can "override" the effects of _outer_ transformers. (This has often seemed unintuitive and "backwards" to me, but that's the way it is.) For example, consider StateT s (FooT ...): if FooT has a failure mode, when a computation fails you don't even get a state anymore. Or if FooT has some sort of backtracking effect, the state will get rewound along with the rest of the computation. On the other hand, FooT (StateT s ....) will still compute a state even when the FooT fails, and the state will be preserved even when the computation backtracks. -Brent
participants (3)
-
Brent Yorgey
-
Michael Mossey
-
Stephen Tetley