MaybeT, guards and run-time pattern matching failure

I'm trying to optimize this and I thought that things that return Nothing in the Maybe monad should fail the whole computation sequence. Something subtle is going wrong, I think. MaybeT is at the end of this message. ---- timeout :: forall a.Int -> IO a -> IO (Maybe a) connect_ :: HostName -> Int -> IO Handle startSSL :: IO (SSL, BIO, BIO) type EngineState = MaybeT (WriterT [Log] (StateT World IO)) connect :: [Prop] -> HostName -> Int -> EngineState () connect env h p = do h <- liftIO $ timeout 0 $ connect_ h p -- no complains about this (ssl', tob, fromb) <- liftIO $ timeout 0 startSSL -- bummer, see below ./Script/Engine.hs:101:7: Couldn't match `Maybe (SSL, BIO, BIO)' against `(a, b, c)' Expected type: Maybe (SSL, BIO, BIO) Inferred type: (a, b, c) When checking the pattern: (ssl', tob, fromb) In a 'do' expression: (ssl', tob, fromb) <- liftIO $ (timeout 0 startSSL) ---- I thought I would change it like this: ---- connect env h p = do (Just h) <- liftIO $ timeout 0 $ connect_ h p -- no complains about this ---- but when the connection times out (i'm making it with a delay of 0) I get the following runtime error: *** Exception: Pattern match failure in do expression at ./Script/ Engine.hs:103: So am I stuck with this? ---- connect :: [Prop] -> HostName -> Int -> EngineState () connect env h p = do m'h <- liftIO $ timeout 0 $ connect_ h p m'ssl <- liftIO $ timeout 0 startSSL guard (m'h /= Nothing && m'ssl /= Nothing) -- do I need this?! let h = case m'h of (Just h) -> h let (ssl', tob, fromb) = case m'ssl of a -> a ---- And this is MaybeT: newtype MaybeT m a = MaybeT { runMaybeT :: m (Maybe a) } instance (Monad m) => Monad (MaybeT m) where (MaybeT mon) >>= f = MaybeT (mon >>= maybe (return Nothing) (runMaybeT . f)) return = MaybeT . return . Just instance MonadTrans MaybeT where lift mon = MaybeT (mon >>= return . Just) instance (Monad m) => MonadPlus (MaybeT m) where mzero = MaybeT (return Nothing) mplus (MaybeT a) (MaybeT b) = MaybeT $ do ma <- a mb <- b return $ ma `mplus` mb instance MonadState s m => MonadState s (MaybeT m) where get = lift get put s = lift $ put s instance (MonadIO m) => MonadIO (MaybeT m) where liftIO = lift . liftIO Thanks, Joel -- http://wagerlabs.com/

Joel Reymont wrote:
I'm trying to optimize this and I thought that things that return Nothing in the Maybe monad should fail the whole computation sequence.
No, it shouldn't. 'return Nothing' ist a perfectly valid result of type 'Maybe (Maybe a)', which is not what you want. However, 'mzero' _does_ fail the whole computation and may backtrack into an alternative if you used 'mplus' somewhere.
timeout :: forall a.Int -> IO a -> IO (Maybe a) ... (ssl', tob, fromb) <- liftIO $ timeout 0 startSSL -- bummer, see below
This is quite understandable, as 'timeout ...' gives a 'Maybe (...)' it won't match a tuple. Your second idea is right on point:
(Just h) <- liftIO $ timeout 0 $ connect_ h p -- no complains about this
but when the connection times out (i'm making it with a delay of 0) I get the following runtime error:
A pattern match failure at this point causes 'fail' to be called, which for exactly this reason is a method of class Monad. You didn't define it, therefore you get the default behaviour, and that is to call 'error'. The fix is straight forward:
instance (Monad m) => Monad (MaybeT m) where (MaybeT mon) >>= f = MaybeT (mon >>= maybe (return Nothing) (runMaybeT . f)) return = MaybeT . return . Just fail _ = MaybeT (return Nothing)
Of couse you could also bind the result of 'timeout' to a variable and pattern match on that using 'case'. That gives you more freedom and more ugliness, too. BTW, if you use 'ErrorT' from Control.Monad.Error instead of MaybeT, you also get a nice error message instead of a plain Nothing. Udo.
participants (2)
-
Joel Reymont
-
Udo Stenzel