[Haskell-cafe] Intro to monad transformers

Daniel Fischer daniel.is.fischer at googlemail.com
Sun Dec 26 20:31:05 CET 2010


On Sunday 26 December 2010 20:00:02, michael rice wrote:
> I lifted the code below from here:
>
> http://en.wikibooks.org/wiki/Haskell/Monad_transformers
>
> Since the wiki page doesn't say what needs to be imported, I'm guessing.
>
> Not sure what is happening. Maybe someone can tell me.

It loops trying to show `askPassword'.
You have declared an

instance Show (MaybeT m a)

without defining any methods, so when you type

ghci> askPassword

at the prompt, it tries to print the action, 

putStrLn (show askPassword)

show has a default definition

show x = showsPrec 0 x ""

so it looks for showsPrec, which has a default definition

showsPrec _ x s = show x ++ s

~> loop, that overflows the stack.

Try

ghci> runMaybeT askPassword

>
> Michael
>
> ==============
>
> import Control.Monad
> import Control.Monad.Trans.Class
> import Data.Char
>
> newtype (Monad m) => MaybeT m a = MaybeT { runMaybeT :: m (Maybe a) }
>
> instance Monad m => Monad (MaybeT m) where
>     return  = MaybeT . return . Just
>     x >>= f = MaybeT $ do maybe_value <- runMaybeT x
>                           case maybe_value of
>                                Nothing    -> return Nothing
>                                Just value -> runMaybeT $ f value
>
> instance Monad m => MonadPlus (MaybeT m) where
>     mzero     = MaybeT $ return Nothing
>     mplus x y = MaybeT $ do maybe_value <- runMaybeT x
>                             case maybe_value of
>                                  Nothing    -> runMaybeT y
>                                  Just value -> runMaybeT x
>  
> instance MonadTrans MaybeT where
>     lift = MaybeT . (liftM Just)
>
> instance Show (MaybeT m a)
>
> getValidPassword :: MaybeT IO String
> getValidPassword = do s <- lift getLine
>                       guard (isValid s)
>                       return s
>
> isValid :: String -> Bool
> isValid s = (length s > 8) &&
>             ((filter isAlphaNum  s) == s) &&
>             any isDigit s &&
>             any isAlpha s               
>              
> askPassword :: MaybeT IO ()
> askPassword = do lift $ putStrLn "Insert your new password:"
>                  value <- getValidPassword
>                  lift $ putStrLn "Storing in database..."
>
> =============
>
> [michael at localhost ~]$ ghci
> GHCi, version 6.12.3: http://www.haskell.org/ghc/  :? for help
> Loading package ghc-prim ... linking ... done.
> Loading package integer-gmp ... linking ... done.
> Loading package base ... linking ... done.
> Loading package ffi-1.0 ... linking ... done.
> Prelude> :l test5
> [1 of 1] Compiling Main             ( test5.hs, interpreted )
> Ok, modules loaded: Main.
> *Main> askPassword
> Loading package transformers-0.2.2.0 ... linking ... done.
> *** Exception: stack overflow
> *Main>



More information about the Haskell-Cafe mailing list