Using MonadError within other Monads

Hi, I'm having trouble making use of MonadError within another Monad, in this case IO. I've blundered around for a while, trying various combinations of things, but I don't think I've fully cottoned-on to nesting of monads. Following is some code which does not compile, but hopefully shows you what my intentions are. I'd appreciate it if someone could show me how to use the nested monads in this situation. Thanks. module Test where import Control.Monad.Error import Data.Char import System.IO instance Error Int where noMsg = 1 strMsg = length f :: IO (Either String String) f = do n <- readLn if n == 2 then return $ throwError "I don't like strings with 2 characters." else do s <- mapErrs2 (g n) putStrLn s g :: Int -> IO (Either String String) g 0 = throwError "I won't do zero length strings." g 1 = do c <- getChar c' <- mapErrs (h c) return [c'] g n = do c <- getChar cs <- g (n-1) c' <- mapErrs (h c) return (c':cs) h :: Char -> Either Int Char h c | isUpper c = throwError 200 | otherwise = return $ toUpper c mapErrs :: Either Int Char -> Either String Char mapErrs (Right c) = Right c mapErrs (Left 200) = Left "The String contained uppercase characters." mapErrs (Left i) = Left ("Unrecognised failure in h, code = " ++ (show i)) mapErrs2 :: Either String String -> Either String String mapErrs2 (Right s) = Right s mapErrs2 (Left e) = Left ("g Error: " ++ e)

[It is best to post questions only to haskell-cafe.] On Mon, Dec 19, 2005 at 03:53:53PM +1300, Karl Grapone wrote:
I'm having trouble making use of MonadError within another Monad, in this case IO. I've blundered around for a while, trying various combinations of things, but I don't think I've fully cottoned-on to nesting of monads.
Looking at the signature of f,
f :: IO (Either String String)
"Either String String" is just an ordinary value produced in the IO monad--the monad structure of IO and "Either String" are completely independent. With that in mind, here is a way to make part of your code type-check: g n = do c <- getChar cs <- g (n-1) return $ do c' <- mapErrs (h c) cs' <- cs return (c':cs') The outer do is a computation in the IO monad, the inner do is a computation in the "Either String" monad, and the net effect is an IO computation returning an "Either String" computation--which is just what the type signature says. I had to change your code in 3 other places to make it type-check; hopefully you can now find them. ;-) When people speak of nesting monads, they often mean using monad transformers. If you were using the ErrorT monad transformers, your signature would look like f :: ErrorT String IO String You might want to try rewriting your code that way, but I would suggest making it work with the current type signatures first. Andrew

On 12/19/05, Andrew Pimlott
[It is best to post questions only to haskell-cafe.]
Roger.
On Mon, Dec 19, 2005 at 03:53:53PM +1300, Karl Grapone wrote:
I'm having trouble making use of MonadError within another Monad, in this case IO.
snip
Looking at the signature of f,
f :: IO (Either String String)
"Either String String" is just an ordinary value produced in the IO monad--the monad structure of IO and "Either String" are completely independent. snip The outer do is a computation in the IO monad, the inner do is a computation in the "Either String" monad, and the net effect is an IO computation returning an "Either String" computation--which is just what the type signature says. I had to change your code in 3 other places to make it type-check; hopefully you can now find them. ;-)
No problem, with a little shove in the right direction :). Not entirely sure why I didn't arrive at it myself. I'm using StateT successfully elsewhere and was overeager in using similar methods which, as you point out below, is a different situation. I still find monadic signatures a little confusing, I believe ghci was, at some point, deriving types for f or g that had MonadError in place of Either String, so I'll have to think carefully about why it is so different from the ErrorT type you show below.
When people speak of nesting monads, they often mean using monad transformers. If you were using the ErrorT monad transformers, your signature would look like
f :: ErrorT String IO String
You might want to try rewriting your code that way, but I would suggest making it work with the current type signatures first.
At one point I was playing with types like 'Either String (IO String)', which to me seems very similar to the ErrorT type. Intuitively they don't seem like they'd be correct... I feel like determining that there is an error involves interaction with the outside world, consequently the error part should be inside the IO monad. Now that you've cleared up the simpler case for me I'll try out the ErrorT case. Thanks for the help. Karl

On Mon, Dec 19, 2005 at 10:21:36PM +1300, Karl Grapone wrote:
I still find monadic signatures a little confusing, I believe ghci was, at some point, deriving types for f or g that had MonadError in place of Either String, so I'll have to think carefully about why it is so different from the ErrorT type you show below.
You used throwError, which is a MonadError method, so it's not surprising to get a message about MonadError. Regarding ErrorT...
At one point I was playing with types like 'Either String (IO String)', which to me seems very similar to the ErrorT type.
Actually, your type IO (Either String String) is the same as ErrorT String IO String except for the newtype wrapper. The big difference in use is that the "ErrorT String IO" Monad instance combines the monad structures of IO and Either. So you won't need nested do's, and a few other things will have to change (and you might have to think a bit about mapErrs).
Intuitively they don't seem like they'd be correct... I feel like determining that there is an error involves interaction with the outside world, consequently the error part should be inside the IO monad.
You're correct about that--"Either String (IO String)" is not a monad. Andrew
participants (2)
-
Andrew Pimlott
-
Karl Grapone