
Hi there, Reading http://www.haskell.org/haskellwiki/Things_to_avoid I found an interesting saying: "By the way, in the case of IO monad the Functor class method fmap and the Monad based function liftM are the same." I always tought that prop :: (Functor m, Monad m, Eq (m b)) => (a -> b) -> m a -> Bool prop f x = fmap f x == liftM f x was True regardless of 'm'. Is there any exception? If so, why? I've even done s/fmap/liftM/g and s/liftM/fmap/g in the past for consistency =). Thanks! -- Felipe.

On Mon, 4 Feb 2008, Felipe Lessa wrote:
Hi there,
Reading http://www.haskell.org/haskellwiki/Things_to_avoid I found an interesting saying:
"By the way, in the case of IO monad the Functor class method fmap and the Monad based function liftM are the same."
I always tought that
prop :: (Functor m, Monad m, Eq (m b)) => (a -> b) -> m a -> Bool prop f x = fmap f x == liftM f x
was True regardless of 'm'. Is there any exception? If so, why? I've even done s/fmap/liftM/g and s/liftM/fmap/g in the past for consistency =).
Problem is that from the idea Functor is a superclass of Monad, with the property that "fmap == liftM". The first relation could have been expressed in Haskell 98 but was not done (forgotten?) in the standard libraries. The second relation can even not be expressed in Haskell 98. So it's only cosmetic, if you use 'liftM' instead of 'fmap' in order to avoid an explicit 'Functor' constraint in a function.

Problem is that from the idea Functor is a superclass of Monad, with the property that "fmap == liftM".
[cut]
The second relation can even not be expressed in Haskell 98.
Erm... class Functor f where fmap :: (a -> b) -> f a -> f b class Functor m => Monad m where return :: a -> m a join :: m (m a) -> m a bind :: Monad m => m a -> (a -> m b) -> m b bind mx f = join $ fmap f mx Now liftM must be exactly equal to fmap.

On Mon, 4 Feb 2008, Miguel Mitrofanov wrote:
Problem is that from the idea Functor is a superclass of Monad, with the property that "fmap == liftM".
[cut]
The second relation can even not be expressed in Haskell 98.
Erm...
class Functor f where fmap :: (a -> b) -> f a -> f b class Functor m => Monad m where return :: a -> m a join :: m (m a) -> m a
bind :: Monad m => m a -> (a -> m b) -> m b bind mx f = join $ fmap f mx
nice
Now liftM must be exactly equal to fmap.
How do you convince the compiler that 'join (fmap return x) == x' ?

On Feb 5, 2008, at 8:31 , Henning Thielemann wrote:
How do you convince the compiler that 'join (fmap return x) == x' ?
How do you convince it that the current formulation of Monad obeys the monad laws? (rhetorical) -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

On Tue, 5 Feb 2008, Brandon S. Allbery KF8NH wrote:
On Feb 5, 2008, at 8:31 , Henning Thielemann wrote:
How do you convince the compiler that 'join (fmap return x) == x' ?
How do you convince it that the current formulation of Monad obeys the monad laws? (rhetorical)
My point was that the constraint 'liftM == fmap' cannot be expressed in Haskell 98, and the answer by Miguel suggested that it would be possible by a different design of class Monad. The above was my objection to this suggestion.

Can you do this with a GHC rule? Something like: {-# RULES "join_dot_fmap_return/id" forall x . join (fmap return x) = x #-} Dan Henning Thielemann wrote:
On Tue, 5 Feb 2008, Brandon S. Allbery KF8NH wrote:
On Feb 5, 2008, at 8:31 , Henning Thielemann wrote:
How do you convince the compiler that 'join (fmap return x) == x' ? How do you convince it that the current formulation of Monad obeys the monad laws? (rhetorical)
My point was that the constraint 'liftM == fmap' cannot be expressed in Haskell 98, and the answer by Miguel suggested that it would be possible by a different design of class Monad. The above was my objection to this suggestion. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Feb 5, 2008 6:06 PM, Dan Weston
Can you do this with a GHC rule? Something like:
{-# RULES "join_dot_fmap_return/id" forall x . join (fmap return x) = x #-}
Dan
I guess this would make use of the rule (otherwise the transformation would change the code's semantic) but would not enforce that the rule itself is valid (which is undecidable). Cheers, -- Felipe.

On Tue, 5 Feb 2008, Felipe Lessa wrote:
On Feb 5, 2008 6:06 PM, Dan Weston
wrote: Can you do this with a GHC rule? Something like:
{-# RULES "join_dot_fmap_return/id" forall x . join (fmap return x) = x #-}
Dan
I guess this would make use of the rule (otherwise the transformation would change the code's semantic) but would not enforce that the rule itself is valid (which is undecidable).
I have already thought about (ab)using GHC rules for forcing programmers to take care. :-) That is, if the rule would be stated as above, then programmers _have_ to ensure that the law is satisfied, and the optimizer will penalize violations of the rules with non-working code.

On Feb 6, 2008 11:50 AM, Henning Thielemann
That is, if the rule would be stated as above, then programmers _have_ to ensure that the law is satisfied, and the optimizer will penalize violations of the rules with non-working code.
Be careful. For much less (blowing up when stack > 8MiB) we already had 42 messages =). -- Felipe.

On Mon, 2008-02-04 at 12:22 -0200, Felipe Lessa wrote:
Hi there,
Reading http://www.haskell.org/haskellwiki/Things_to_avoid I found an interesting saying:
"By the way, in the case of IO monad the Functor class method fmap and the Monad based function liftM are the same."
I always tought that
prop :: (Functor m, Monad m, Eq (m b)) => (a -> b) -> m a -> Bool prop f x = fmap f x == liftM f x
was True regardless of 'm'. Is there any exception?
If there is, it's a bug in the library except you wouldn't normally use (==) but some meta-level equality*. From one perspective, liftM is the proof that every monad is a functor. * Usually observational equality, but one may want variants, e.g. observational equality with respect to some "observe" function

On 4 Feb 2008, at 6:22 AM, Felipe Lessa wrote:
Hi there,
Reading http://www.haskell.org/haskellwiki/Things_to_avoid I found an interesting saying:
"By the way, in the case of IO monad the Functor class method fmap and the Monad based function liftM are the same."
I always tought that
prop :: (Functor m, Monad m, Eq (m b)) => (a -> b) -> m a -> Bool prop f x = fmap f x == liftM f x
Indeed, this is an equation from the equivalence of Haskell and category-theoretic monads. Furthermore, the same thing is explicitly asserted by the Haskell 98 Report: [1] Instances of both Monad and Functor should additionally satisfy the law: fmap f xs = xs >>= return . f
was True regardless of 'm'. Is there any exception?
There is only one case I'm aware of: if the author of the type forgot to define a functor instance for his monad (I've been guilty of that before, at least). jcc (I fixed the wiki, btw.) [1] http://haskell.org/onlinereport/basic.html#sect6.3.6
participants (7)
-
Brandon S. Allbery KF8NH
-
Dan Weston
-
Derek Elkins
-
Felipe Lessa
-
Henning Thielemann
-
Jonathan Cast
-
Miguel Mitrofanov