
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 ============== 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>

On 26 December 2010 19:00, 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.
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
I haven't run the code but the definition of mplus here looks cyclic.

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 _ -> return maybe_value
I've not run it so with some caution, I'd expect this to work - the last line is now returning the first answer with 'return' of the wrapped monad. I'm not sure if this is a lawful version of mplus though...

On Sun, Dec 26, 2010 at 2:00 PM, michael rice
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
The last line is wrong. It should be, "Just value -> return value". But that doesn't cause the problem.
instance Show (MaybeT m a)
This is never valid. You've defined show, shows, and showsPrec in terms of each other, creating unbounded recursion. Delete it.
*Main> askPassword Loading package transformers-0.2.2.0 ... linking ... done. *** Exception: stack overflow
This triggers the unbounded recursion, when it tries to show askPassword.
Note that there is no way to show IO values, so there's no way to show
MaybeT IO values.
Instead, use runMaybeT askPassword
--
Dave Menendez

On Sun, 26 Dec 2010, David Menendez wrote:
instance Show (MaybeT m a)
This is never valid. You've defined show, shows, and showsPrec in terms of each other, creating unbounded recursion. Delete it.
Unfortunately, the -Wall option of GHC won't help here, since all the methods are defined by default methods.

Ok, changed the last line and deleted the bad line. Maybe someone could recommend a better example?
Michael
=============
Prelude> :l test5
[1 of 1] Compiling Main ( test5.hs, interpreted )
test5.hs:16:4:
Occurs check: cannot construct the infinite type: a = Maybe a
When generalising the type(s) for `mplus'
In the instance declaration for `MonadPlus (MaybeT m)'
Failed, modules loaded: none.
--- On Sun, 12/26/10, David Menendez

On Sunday 26 December 2010 21:21:00, michael rice wrote:
Ok, changed the last line and deleted the bad line. Maybe someone could recommend a better example?
Michael
=============
Prelude> :l test5 [1 of 1] Compiling Main ( test5.hs, interpreted )
test5.hs:16:4: Occurs check: cannot construct the infinite type: a = Maybe a When generalising the type(s) for `mplus' In the instance declaration for `MonadPlus (MaybeT m)' Failed, modules loaded: none.
mplus x y = MaybeT $ do maybe_value <- runMaybeT x
case maybe_value of Nothing -> runMaybeT y Just value -> runMaybeT x
The last line is wrong. It should be, "Just value -> return value".
Actually, it should be case maybe_value of Nothing -> runMaybeT y _ -> return maybe_value

Ok, that works. On to code reading and, hopefully, enlightenment.
Thanks, all.
Michael
--- On Sun, 12/26/10, Daniel Fischer
Ok, changed the last line and deleted the bad line. Maybe someone could recommend a better example?
Michael
=============
Prelude> :l test5 [1 of 1] Compiling Main ( test5.hs, interpreted )
test5.hs:16:4: Occurs check: cannot construct the infinite type: a = Maybe a When generalising the type(s) for `mplus' In the instance declaration for `MonadPlus (MaybeT m)' Failed, modules loaded: none.
mplus x y = MaybeT $ do maybe_value <- runMaybeT x
case maybe_value of Nothing -> runMaybeT y Just value -> runMaybeT x
The last line is wrong. It should be, "Just value -> return value".
Actually, it should be case maybe_value of Nothing -> runMaybeT y _ -> return maybe_value

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@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>
participants (5)
-
Daniel Fischer
-
David Menendez
-
Henning Thielemann
-
michael rice
-
Stephen Tetley