Re: [Haskell-cafe] Intro to monad transformers

On Dec 26, 2010 2:01 PM, "michael rice"
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.
Michael
I haven't had a chance to dig into your example, but you might want to try the maybeT library: http://hackage.haskell.org/package/MaybeT That way you could try to narrow down where the error is coming from. Take care, Antoine
==============
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@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>
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Sun, 26 Dec 2010, Antoine Latter wrote:
I haven't had a chance to dig into your example, but you might want to try the maybeT library:
http://hackage.haskell.org/package/MaybeT
That way you could try to narrow down where the error is coming from.
MaybeT is also part of transformers library now. http://hackage.haskell.org/packages/archive/transformers/0.2.2.0/doc/html/Co...
participants (2)
-
Antoine Latter
-
Henning Thielemann