[Haskell-cafe] Making monadic code more concise

lyang lyang at cs.stanford.edu
Mon Nov 15 14:42:39 EST 2010


> This, to me, is a big hint that applicative functors could be useful.   

Indeed, the ideas here also apply to applicative functors; it is just the lifting primitives that will be different; instead of having liftM<N>, we can use <$> and <*> to lift the functions. We could have done this for Num and Maybe (suppose Maybe is an instance of Applicative):

instance (Num a) => Num (Maybe a) where
	(+) = \x y -> (+) <$> x <*> y
	(-) = \x y -> (-) <$> x <*> y
	(*) = \x y -> (+) <$> x <*> y
	abs = abs <$>
	signum = signum <$>
	fromInteger = pure . fromInteger

The larger goal remains the same: autolifting in a principled manner.

However, you actually bring up a very good point; what if it is really only the applicative functors that this method works on in general, that there is no 'use case' for considering this autolifting for monads in particular?
I think the answer lies in the fact that monads can be 'flattened;' that is, realizations of the type m (m a) -> m a are mechanical (in the form of 'join') given that >>= is defined. This is important when we have a typeclass that also has monadic signatures. To be more concrete, consider how this function could be used in a 'monadic DSL':

enter x = case x of
	0 -> Nothing
	_ -> Just "hi"

The type of 'enter' is one case of the general from 'a -> M b'. If we were instancing a typeclass that had an 'a -> M b' function, we'd need a function of type 'M a -> M b'. This would be accomplished by 

enter' = join . liftM enter

So the set of lifting primitives must include at least some way to get M a -> M b from 'a -> M b'---which requires that M is a monad, not just an applicative functor.

Thanks for the mention of applicative functors; I should have included them in the original post.

Lingfeng Yang
lyang at cs dot stanford dot edu

-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20101115/641b19ee/attachment.html


More information about the Haskell-Cafe mailing list