[Haskell-cafe] Two-continuation `monads' and MonadMinus [Re: Parsers are monadic?]

David Menendez zednenem at psualum.com
Fri Jul 6 16:14:37 EDT 2007


oleg at pobox.com writes:

> 
> Called MonadMinus, it is capable of defining LogicT monad with the
> true logical negation as well as interleaving and committed choice.
> Our ICFP05 paper describes MonadMinus monad (actually, the
> transformer) and LogicT as well as their two implementations.

I just noticed that the Haskell wiki[1] claims that Data.Foldable
generalizes MonadMinus (aka MonadSplit).

    [1] <http://www.haskell.org/haskellwiki/New_monads>
    
It's true that you can define msplit in terms of foldr, e.g.:
    
    msplit :: (Foldable m, MonadPlus m) => m a -> m (Maybe (a, m a))
    msplit a = foldr sk (return Nothing) a
        where sk a m = return (Just (a, reflect m))

    reflect :: MonadPlus m => m (Maybe (a, m a)) -> m a
    reflect m = m >>= maybe mzero (\(a,m') -> return a `mplus` m')

But I can't help but feel that something is being lost.

I was initially skeptical about defining Foldable for the direct-style
LogicT transformer, but now I suspect that it is definable.
-- 
David Menendez <zednenem at psualum.com> | "In this house, we obey the laws
<http://www.eyrie.org/~zednenem>      |        of thermodynamics!"


More information about the Haskell-Cafe mailing list