
Hi, I can desugar do x' <- x f x' as x >>= \x -> f x' which is clearly the same as x >>= f However, now consider do x' <- x y' <- y f x' y' desugared, this is x >>= \x -> y >>= \y' -> f x' y' I can simplify the second half to x >>= \x -> y >>= f x' but now we are stuck. I feel it should be possible to write something like x ... y ... f or perhaps f ... x ... y the best I could come up with was join $ return f `ap` x `ap` y which is not terrible but quite as easy as I feel this should be. Any hints? Edsko

Check out liftM2. It's almost what you want.
On Thu, Feb 12, 2009 at 6:36 PM, Edsko de Vries
Hi,
I can desugar
do x' <- x f x'
as
x >>= \x -> f x'
which is clearly the same as
x >>= f
However, now consider
do x' <- x y' <- y f x' y'
desugared, this is
x >>= \x -> y >>= \y' -> f x' y'
I can simplify the second half to
x >>= \x -> y >>= f x'
but now we are stuck. I feel it should be possible to write something like
x ... y ... f
or perhaps
f ... x ... y
the best I could come up with was
join $ return f `ap` x `ap` y
which is not terrible but quite as easy as I feel this should be. Any hints?
Edsko _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Thu, 2009-02-12 at 23:36 +0000, Edsko de Vries wrote:
Hi,
I can desugar
do x' <- x f x'
as
x >>= \x -> f x'
which is clearly the same as
x >>= f
However, now consider
do x' <- x y' <- y f x' y'
desugared, this is
x >>= \x -> y >>= \y' -> f x' y'
I can simplify the second half to
x >>= \x -> y >>= f x'
but now we are stuck. I feel it should be possible to write something like
x ... y ... f
or perhaps
f ... x ... y
the best I could come up with was
join $ return f `ap` x `ap` y
which is not terrible but quite as easy as I feel this should be. Any hints?
Copying a bit of Applicative style, you could say join $ f `liftM` x `ap` y I've thought it would be nice to have something like app :: Monad m => m (a -> m b) -> m a -> m b app af ax = join $ af `ap` ax in the standard library. Then you could simplify to f `liftM` x `app` y I think that's as simple as you're going to get. For more arguments, say f `liftM` x `ap` y `app` z The rule is: first application operator is `liftM` (or <$> --- I always define Applicative instances for my monads); last application operator is `app`; the operators in-between are all `ap`. I think that's a pretty straight-forward rule to follow. jcc

Hello, You could do: (f =<< x) =<< y ? - jeremy At Thu, 12 Feb 2009 23:36:19 +0000, Edsko de Vries wrote:
Hi,
I can desugar
do x' <- x f x'
as
x >>= \x -> f x'
which is clearly the same as
x >>= f
However, now consider
do x' <- x y' <- y f x' y'
desugared, this is
x >>= \x -> y >>= \y' -> f x' y'
I can simplify the second half to
x >>= \x -> y >>= f x'
but now we are stuck. I feel it should be possible to write something like
x ... y ... f
or perhaps
f ... x ... y
the best I could come up with was
join $ return f `ap` x `ap` y
which is not terrible but quite as easy as I feel this should be. Any hints?
Edsko _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

oops, I take that back. It only appears to work if you are sloppy: x :: (Monad m) => m a x = undefined y :: (Monad m) => m b y = undefined g :: (Monad m) => a -> b -> m c g = undefined ex1 :: (Monad m) :: m c ex1 = (g =<< x) =<< y But, if you try to pin down the types you find it only works because they are not all the same Monad m. a :: (Int -> Int) a = return 1 b :: Maybe Int b = Just 2 h :: Int -> Int -> Maybe Int h a b = return (a + b) ex5 :: Maybe Int ex5 = (h =<< a) =<< b :) j. At Thu, 12 Feb 2009 18:04:45 -0600, Jeremy Shaw wrote:
Hello,
You could do:
(f =<< x) =<< y
?
- jeremy
At Thu, 12 Feb 2009 23:36:19 +0000, Edsko de Vries wrote:
Hi,
I can desugar
do x' <- x f x'
as
x >>= \x -> f x'
which is clearly the same as
x >>= f
However, now consider
do x' <- x y' <- y f x' y'
desugared, this is
x >>= \x -> y >>= \y' -> f x' y'
I can simplify the second half to
x >>= \x -> y >>= f x'
but now we are stuck. I feel it should be possible to write something like
x ... y ... f
or perhaps
f ... x ... y
the best I could come up with was
join $ return f `ap` x `ap` y
which is not terrible but quite as easy as I feel this should be. Any hints?
Edsko _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hey, Thanks for all the suggestions. I was hoping that there was some uniform pattern that would extend to n arguments (rather than having to use liftM2, litM3, etc. or have different 'application' operators in between the different arguments); perhaps not. Oh well :) Thanks again! Edsko

Hi Edsko On 13 Feb 2009, at 09:14, Edsko de Vries wrote:
Hey,
Thanks for all the suggestions. I was hoping that there was some uniform pattern that would extend to n arguments (rather than having to use liftM2, litM3, etc. or have different 'application' operators in between the different arguments); perhaps not. Oh well :)
Will this do? http://www.haskell.org/haskellwiki/Idiom_brackets You get to write iI f a1 a2 a3 Ji for do x1 <- a1 x2 <- a2 x3 <- a3 f a1 a2 a3 amongst other things... Cheers Conor This message has been checked for viruses but the contents of an attachment may still contain software viruses, which could damage your computer system: you are advised to perform your own checks. Email communications with the University of Nottingham may be monitored as permitted by UK legislation.

Hey,
Thanks for all the suggestions. I was hoping that there was some uniform pattern that would extend to n arguments (rather than having to use liftM2, litM3, etc. or have different 'application' operators in between the different arguments); perhaps not. Oh well :)
Sure you can! What you want is Control.Applicative, not Control.Monad. (<*>) is the generic application you're looking for:
pure (+) <*> [1,2,3] <*> [4,5,6] [5,6,7,6,7,8,7,8,9]
Note that pure f <*> y can be shortened to fmap though, which Control.Applicative defines a handy infix version of:
(+) <$> [1,2,3] <*> [4,5,6] [5,6,7,6,7,8,7,8,9]
Hope that provides what you want Bob

On Fri, Feb 13, 2009 at 05:21:50PM +0100, Thomas Davie wrote:
Hey,
Thanks for all the suggestions. I was hoping that there was some uniform pattern that would extend to n arguments (rather than having to use liftM2, litM3, etc. or have different 'application' operators in between the different arguments); perhaps not. Oh well :)
Sure you can! What you want is Control.Applicative, not Control.Monad.
(<*>) is the generic application you're looking for:
pure (+) <*> [1,2,3] <*> [4,5,6] [5,6,7,6,7,8,7,8,9]
Note that pure f <*> y can be shortened to fmap though, which Control.Applicative defines a handy infix version of:
(+) <$> [1,2,3] <*> [4,5,6] [5,6,7,6,7,8,7,8,9]
Hope that provides what you want
Hi Bob, Thanks for the suggestion, but that solution does not work when the function I want to apply (in your case, +) is monadic itself. Then I'd still have to write join $ f <*> [1,2,3] <*> [4,5,6] :( Edsko

Hi Conor,
Will this do?
http://www.haskell.org/haskellwiki/Idiom_brackets
You get to write
iI f a1 a2 a3 Ji
for
do x1 <- a1 x2 <- a2 x3 <- a3 f a1 a2 a3
amongst other things...
Cool :-) I had seen those idiom brackets before and put them on my mental 'things I want to understand' list but never got round to them. Very nice! Now if only ghc would allow me to write unicode so that I can write *real* brackets.. (Something the Agda people do very well!) Thanks! Edsko
participants (6)
-
Andrew Wagner
-
Conor McBride
-
Edsko de Vries
-
Jeremy Shaw
-
Jonathan Cast
-
Thomas Davie