[Haskell-cafe] Using MonadError within other Monads

Karl Grapone kgrapone at gmail.com
Sun Dec 18 21:53:53 EST 2005


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)


More information about the Haskell-Cafe mailing list