[Haskell-cafe] nested maybes

Donald Bruce Stewart dons at cse.unsw.edu.au
Sun Feb 4 18:39:34 EST 2007


u.stenzel:
> J. Garrett Morris wrote:
> > On 2/4/07, Udo Stenzel <u.stenzel at web.de> wrote:
> > >> exists s wmap = isJust $ Map.lookup (sort s) wmap >>= find (== s) . snd
> > 
> > If you're going to write it all on one line, I prefer to keep things
> > going the same direction:
> 
> Hey, doing it this way saved me a full two keystrokes!!!1
> 
> Sure, you're right, everything flowing in the same direction is usually
> nicer, and in central Europe, that order is from the left to the right.
> What a shame that the Haskell gods chose to give the arguments to (.)
> and ($) the wrong order!
> 
> > exists s wmap = isJust $ find (==s) . snd =<< Map.lookup (sort s) wmap
> > 
> > Normally, from there I would be tempted to look for a points-free
> > implementation, but in this case I have a strong suspicion that would
> > simply be unreadable.
> 
> Well, depends on whether we are allowed to define new combinators.  I
> sometimes use
> 
> -- Kleisli composition
> infixl 1 @@
> (@@) :: Monad m => (a -> m b) -> (b -> m c) -> (a -> m c)
> f @@ g = join . liftM g . f

By the way, this is now in Control.Monad (in darcs). Though since we
also want the flipped version, it becomes:

    -- | Left-to-right Kleisli composition of monads.
    (>=>)       :: Monad m => (a -> m b) -> (b -> m c) -> (a -> m c)
    f >=> g     = \x -> f x >>= g

    -- | Right-to-left Kleisli composition of monads. '(>=>)', with the
    arguments flipped
    (<=<)       :: Monad m => (b -> m c) -> (a -> m b) -> (a -> m c)
    (<=<)       = flip (>=>)

Cheers,
  Don


More information about the Haskell-Cafe mailing list