[Haskell-cafe] Indentation Creep
Dan Doel
dan.doel at gmail.com
Fri Jul 13 20:19:03 EDT 2007
In addition to what's already been pointed out, note that this:
> do t <- readTVar p
> case t of
> Empty -> return Nothing
> Trie l m r -> do <stuff>
Is a case of the (non-existent) MaybeT transformer:
> do Trie l m r <- readTVar p
> <stuff with slight modifications>
The modifications being something like 'return . Just' => 'return',
and 'return Nothing' => mzero.
> newtype MaybeT m a = MaybeT { runMaybeT :: m (Maybe a) }
> instance Functor f => Functor (MaybeT f) where
> fmap f = MaybeT . fmap (fmap f) . runMaybeT
> instance Monad m => Monad (MaybeT m) where
> return = MaybeT . return . Just
> m >>= f = MaybeT $ runMaybeT m >>= (runMaybeT . f)
> fail _ = MaybeT $ return Nothing
> instance Monad m => MonadPlus (MaybeT m) where
> mzero = MaybeT $ return Nothing
> m1 `mplus` m2 = MaybeT $ liftM2 mplus (runMaybeT m1) (runMaybeT m2)
(I haven't tested the code, but that's approximately what it looks like; let
me know if I did something wrong and you need it fixed; I suspect you won't,
as I'm not sure it simplifies the remained of <stuff> any :))
-- Dan
More information about the Haskell-Cafe
mailing list