Functor => Pointed => Applicative => Monad

Maciej Piechotka uzytkownik2 at gmail.com
Mon Nov 29 14:58:41 CET 2010


On Mon, 2010-11-29 at 10:39 +0200, John Smith wrote:
> Is there any intention to reorganise the standard class hierarchy, arranging them logically instead of in order of 
> invention? I plagiarised the following example from 
> http://stackoverflow.com/questions/1634911/can-liftm-differ-from-lifta and Trac:
> 
> class Functor f where
>      map :: (a -> b) -> f a -> f b
> 
> class Functor f => Pointed f where
>      pure :: a -> f a
> 
> class Pointed f => Applicative f where
>      (<*>) :: f (a -> b) -> f a -> f b
>      (*>) :: f a -> f b -> f b
>      (<*) :: f a -> f b -> f a

    a *> b = flip const <$> a <*> b
    a <* b = const <$> a <*> b

> 
> class Applicative m => Monad m where
>      (>>=) :: m a -> (a -> m b) -> m b
>      (>>) :: m a -> m b -> m b
>      join :: m (m a) -> m a
> 
>      f >>= x = join (fmap f x)
>      m >> k = m >>= \_ -> k
>      join x = x >>= id
> 
> This would eliminate the necessity of declaring a Monad instance for every Applicative, and eliminate the need for sets 
> of duplicate functions such as [fmap,liftM,map,liftA], [(<*>),ap], and [concat,join].
> 

Technically (>>) and (*>) are duplicates assumin (<*>) and ap are, I
believe:


a *> b
flip const <$> a <*> b
(fmap (flip const) a) <*> b
ap (fmap (flip const) a) b
liftM2 id (fmap (flip const) a) b
(fmap (flip const) a) >>= \a' -> b >>= \b' -> return (id a' b')
(fmap (flip const) a) >>= \a' -> b >>= \b' -> return (a' b')
a >>= \a' -> b >>= \b' -> return (flip const a' b')
a >>= \a' -> b >>= \b' -> return (const b' a')
a >>= \a' -> b >>= \b' -> return b'
a >>= \a' -> b
a >>= \_ -> b
a >> b

> fail should be removed from Monad; a failed pattern match could error in the same way as is does for pure code. The only 
> sensible uses for fail seem to be synonyms for mzero.

It is discussed for some time on mailing list. However I'm not aware
about any movement in this direction.

Probably it is because that the Monad is in core of many Haskell
libraries from which some do not define Applicative. Possibly it could
be tested on Hackage how big impact would be to current packages.

Other method would be to have "weak instances" (we inform compiler that
the legal, unoptimized implementation must look like this but allow
overwritten for performance). Something like:

instance weak Monad a => Functor a where
    fmap = liftM

instance weak Monad a => Pointed a where
    point = return

instance weak Monad a => Applicative a where
    (<*>) = `ap`

Regards
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 836 bytes
Desc: This is a digitally signed message part
Url : http://www.haskell.org/pipermail/libraries/attachments/20101129/8fe205ed/attachment.bin


More information about the Libraries mailing list