
i came across hlint today and ran it on my experiments. It pointed out places where I was overly cautious with parens or used a $ and forget to remove it later. But one suggestion it made I was curious about. Why does it recommend using fmap over >>=? Idiomatically does fmap make more sense when the Monad is more like a collection? For instance I had "(applyOp op x y) >>= (flip (:) ds)". This seems more clear than "fmap ((:) ds) (applyOp op x y)".

On Mon, May 2, 2011 at 8:56 PM, Sean Perry
i came across hlint today and ran it on my experiments. It pointed out places where I was overly cautious with parens or used a $ and forget to remove it later. But one suggestion it made I was curious about.
Why does it recommend using fmap over >>=? Idiomatically does fmap make more sense when the Monad is more like a collection?
For instance I had "(applyOp op x y) >>= (flip (:) ds)". This seems more clear than "fmap ((:) ds) (applyOp op x y)".
Part of the reason for the suggestion is that bind is "more powerful" than fmap, which means that it asks more of the implementing type, which then means that fewer type satisfy bind than satisfy fmap. So your function is more general when written using fmap. I might write this with the infix version of fmap, but some folks don't like the explosion of operators:
((:) ds) <$> applyOp op x y
or closer to yours:
flip (:) ds <$> applyOp op x y
If the type of the function is already fixed I think it comes down to personal preference. Antoine
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Mon, May 2, 2011 at 11:14 PM, Antoine Latter
Part of the reason for the suggestion is that bind is "more powerful" than fmap, which means that it asks more of the implementing type, which then means that fewer type satisfy bind than satisfy fmap. So your function is more general when written using fmap.
And depending on the data type, 'f <$> m' may be more efficient than 'm >>= return . f'
I might write this with the infix version of fmap, but some folks don't like the explosion of operators:
((:) ds) <$> applyOp op x y
Note that this should be "(: ds) <$> applyOp op x y". I mean, (:) ds === (ds :) flip (:) ds === (\x -> x : ds) === (: ds)
or closer to yours:
flip (:) ds <$> applyOp op x y
If the type of the function is already fixed I think it comes down to personal preference.
Applicative style is very nice, specially when your functions have multiple arguments. Consider op1 >>= \x1 -> op2 >>= \x2 -> return (f x1 x2) do {x1 <- op1 x2 <- op2 return (f x1 x2)} against f <$> op1 <*> op2 Cheers, -- Felipe.

Hi all,
On Mon, May 2, 2011 at 9:56 PM, Sean Perry
i came across hlint today and ran it on my experiments. It pointed out places where I was overly cautious with parens or used a $ and forget to remove it later. But one suggestion it made I was curious about.
Why does it recommend using fmap over >>=? Idiomatically does fmap make more sense when the Monad is more like a collection?
For instance I had "(applyOp op x y) >>= (flip (:) ds)". This seems more clear than "fmap ((:) ds) (applyOp op x y)".
I'm trying to understand this example and I can't get the types to line up. Can you provide the "real" types for ds and (applyOp op x y)? This is what I'm working out: fmap ((:) ds) (applyOp op x y) == fmap (ds :) (applyOp op x y) == fmap (\dss -> ds : dss) (applyOp op x y) (applyOp op x y) >>= (flip (:) ds) == (applyOp op x y) >>= (: ds) == (applyOp op x y) >>= (\d -> d : ds) To my untrained eyes is doesn't even look like the code is doing the same thing... What am I missing here (or more probably where is my mistake)? Patrick
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- ===================== Patrick LeBoutillier Rosemère, Québec, Canada

On Tue, May 3, 2011 at 12:32 PM, Patrick LeBoutillier
I'm trying to understand this example and I can't get the types to line up. Can you provide the "real" types for ds and (applyOp op x y)?
This is what I'm working out:
fmap ((:) ds) (applyOp op x y) == fmap (ds :) (applyOp op x y) == fmap (\dss -> ds : dss) (applyOp op x y)
(applyOp op x y) >>= (flip (:) ds) == (applyOp op x y) >>= (: ds) == (applyOp op x y) >>= (\d -> d : ds)
To my untrained eyes is doesn't even look like the code is doing the same thing... What am I missing here (or more probably where is my mistake)?
I think that OP forgot a return, i.e., he meant 'applyOp op x y >>= return . flip (:) ds'. Regardless, there's a trick that you may use whenever you want to know the types of something. Just make a function where everything you don't know is an argument, and ask GHCi to give you its type. Supposing it's Haskell 98, GHCi will always give you the most general type. With this example: Prelude> :t \ds applyOp op x y -> applyOp op x y >>= flip (:) ds \ds applyOp op x y -> applyOp op x y >>= flip (:) ds :: [a] -> (t -> t1 -> t2 -> [a]) -> t -> t1 -> t2 -> [a] So we see that ds :: [a] applyOp :: t -> u -> v -> [a] op :: t x :: u y :: v applyOp op x y >>= flip (:) ds :: [a] works. In other words, it's an expression in the list monad. Whether it is useful or not, I don't know =). Adding the 'return': Prelude> :t \ds applyOp op x y -> applyOp op x y >>= return . flip (:) ds \ds applyOp op x y -> applyOp op x y >>= return . flip (:) ds :: (Monad m) => [a] -> (t -> t1 -> t2 -> m a) -> t -> t1 -> t2 -> m [a] So now we get: Monad m => ds :: [a] applyOp :: t -> u -> v -> m a op :: t x :: u y :: v applyOp op x y >>= return . flip (:) ds :: m [a] Seems much more useful! So 'applyOp op x y :: m a' and the result of everything is 'm [a]'. Note that if there is a type mismatch (even with the general arguments!), GHCi will tell you right away. For example, Prelude> :t \ds applyOp op x y -> applyOp op x y >>= fmap . flip (:) ds <interactive>:1:48: Couldn't match expected type `a -> b' against inferred type `[a1]' In the second argument of `(.)', namely `flip (:) ds' In the second argument of `(>>=)', namely `fmap . flip (:) ds' In the expression: applyOp op x y >>= fmap . flip (:) ds This means that no matter what ds, applyOp, op, x and y you choose, 'applyOp op x y >>= fmap . flip (:) ds' will always be ill-typed. Cheers, -- Felipe.

Felipe,
Regardless, there's a trick that you may use whenever you want to know the types of something. Just make a function where everything you don't know is an argument, and ask GHCi to give you its type.
That's a great trick. Thanks everybody for your help. Patrick
Supposing it's Haskell 98, GHCi will always give you the most general type. With this example:
Prelude> :t \ds applyOp op x y -> applyOp op x y >>= flip (:) ds \ds applyOp op x y -> applyOp op x y >>= flip (:) ds :: [a] -> (t -> t1 -> t2 -> [a]) -> t -> t1 -> t2 -> [a]
So we see that
ds :: [a] applyOp :: t -> u -> v -> [a] op :: t x :: u y :: v applyOp op x y >>= flip (:) ds :: [a]
works. In other words, it's an expression in the list monad. Whether it is useful or not, I don't know =). Adding the 'return':
Prelude> :t \ds applyOp op x y -> applyOp op x y >>= return . flip (:) ds \ds applyOp op x y -> applyOp op x y >>= return . flip (:) ds :: (Monad m) => [a] -> (t -> t1 -> t2 -> m a) -> t -> t1 -> t2 -> m [a]
So now we get:
Monad m => ds :: [a] applyOp :: t -> u -> v -> m a op :: t x :: u y :: v applyOp op x y >>= return . flip (:) ds :: m [a]
Seems much more useful! So 'applyOp op x y :: m a' and the result of everything is 'm [a]'.
Note that if there is a type mismatch (even with the general arguments!), GHCi will tell you right away. For example,
Prelude> :t \ds applyOp op x y -> applyOp op x y >>= fmap . flip (:) ds
<interactive>:1:48: Couldn't match expected type `a -> b' against inferred type `[a1]' In the second argument of `(.)', namely `flip (:) ds' In the second argument of `(>>=)', namely `fmap . flip (:) ds' In the expression: applyOp op x y >>= fmap . flip (:) ds
This means that no matter what ds, applyOp, op, x and y you choose, 'applyOp op x y >>= fmap . flip (:) ds' will always be ill-typed.
Cheers,
-- Felipe.
-- ===================== Patrick LeBoutillier Rosemère, Québec, Canada

On Tuesday 03 May 2011 17:32:14, Patrick LeBoutillier wrote:
Hi all,
On Mon, May 2, 2011 at 9:56 PM, Sean Perry
wrote: i came across hlint today and ran it on my experiments. It pointed out places where I was overly cautious with parens or used a $ and forget to remove it later. But one suggestion it made I was curious about.
Why does it recommend using fmap over >>=? Idiomatically does fmap make more sense when the Monad is more like a collection?
For instance I had "(applyOp op x y) >>= (flip (:) ds)". This seems more clear than "fmap ((:) ds) (applyOp op x y)".
I'm trying to understand this example and I can't get the types to line
Right, they don't match. As first argument of (>>=), we must have applyOp op x y :: m a, where m is some monad. flip (:) ds = (: ds) = \x -> x:ds :: a -> [a], where ds :: [a]. So m = [], applyOp op x y :: [a] applyOp op x y >>= flip (:) ds :: [a] On the other hand, assuming the flip has just been forgotten while typing, fmap :: (a -> b) -> [a] -> [b] (using the specific Functor of this example), the fmapped function has type (a -> [a]), so fmap (flip (:) ds) (applyOp op x y) :: [[a]] There's a concat missing here, or a return in the (>>=) piece to make the types fit. If the omission of flip in the fmap is not accidental, there's more amiss.
up. Can you provide the "real" types for ds and (applyOp op x y)?
This is what I'm working out:
fmap ((:) ds) (applyOp op x y) == fmap (ds :) (applyOp op x y) == fmap (\dss -> ds : dss) (applyOp op x y)
(applyOp op x y) >>= (flip (:) ds) == (applyOp op x y) >>= (: ds) == (applyOp op x y) >>= (\d -> d : ds)
To my untrained eyes is doesn't even look like the code is doing the same thing... What am I missing here (or more probably where is my mistake)?
Patrick
participants (5)
-
Antoine Latter
-
Daniel Fischer
-
Felipe Almeida Lessa
-
Patrick LeBoutillier
-
Sean Perry