Proposal: Add default instances for Functor and Applicative

The problem of backward compatibility have been the main obstacle against adopting Functor f => (Pointed f =>?) => Applicative f => Monad f. This proposition is to add following default instances[1]: default fmap :: Applicative f => (a -> b) -> f a -> f b f `fmap` m = pure f <*> m default pure :: Monad f => a -> f a pure = return default (<*>) :: Monad f => f (a -> b) -> f a -> f b (<*>) = liftM2 ($) The proposition is intended as step towards implementing whole hierarchy of Functor f => (Pointed f =>?) => Applicative f => Monad f[2] Discussion period: 2 weeks Regards [1] It's using DefaultSuperclassInstances extentions: http://hackage.haskell.org/trac/ghc/wiki/DefaultSuperclassInstances [2] Trivial implementation is shown here: http://thread.gmane.org/gmane.comp.lang.haskell.libraries/16196 I believe that in such case the Pointed instance comes at nearly zero cost.

On 23 September 2011 21:25, Maciej Marcin Piechotka
The problem of backward compatibility have been the main obstacle against adopting Functor f => (Pointed f =>?) => Applicative f => Monad f.
This proposition is to add following default instances[1]:
Sorry, I'm confused! The [1] link is about default superclass instances, not default signatures. As I understand it, default superclass instances are not implemented yet. I fully support the general aim and default superclass instances look like a very sensible way of addressing the problem. It's just not clear to me how the default signatures you're suggesting here get us closer to the goal. Perhaps you can explain it a bit more. I suspect other people on this list don't quite get it either.
default fmap :: Applicative f => (a -> b) -> f a -> f b f `fmap` m = pure f <*> m default pure :: Monad f => a -> f a pure = return default (<*>) :: Monad f => f (a -> b) -> f a -> f b (<*>) = liftM2 ($)
Duncan

On Fri, 2011-09-23 at 23:46 +0100, Duncan Coutts wrote:
On 23 September 2011 21:25, Maciej Marcin Piechotka
wrote: The problem of backward compatibility have been the main obstacle against adopting Functor f => (Pointed f =>?) => Applicative f => Monad f.
This proposition is to add following default instances[1]:
Sorry, I'm confused! The [1] link is about default superclass instances, not default signatures. As I understand it, default superclass instances are not implemented yet.
Ups. You're right.
I fully support the general aim and default superclass instances look like a very sensible way of addressing the problem. It's just not clear to me how the default signatures you're suggesting here get us closer to the goal.
Perhaps you can explain it a bit more. I suspect other people on this list don't quite get it either.
From example in link [2]. If we had:
class Functor f where fmap :: (a -> b) -> f a -> f b default fmap :: Applicative f => (a -> b) -> f a -> f b f `fmap` m = pure f <*> m (<$) :: a -> f b -> f a (<$) = fmap . const
class Functor f => Pointed f where point :: a -> f a default point :: Applicative f => a -> f a point = pure
class Pointed f => Applicative f where pure :: a -> f a default pure :: Monad f => a -> f a pure = return (<*>) :: f (a -> b) -> f a -> f b default (<*>) :: Monad f => f (a -> b) -> f a -> f b f <*> v = liftM2 ($) f v (*>) :: f a -> f b -> f b (*>) = liftA2 (const id) (<*) :: f a -> f b -> f a (<*) = liftA2 const
class Applicative f => Monad f where return :: a -> f a (>>=) :: f a -> (a -> f b) -> f b (>>) :: f a -> f b -> f b m >> k = m >>= const k
Then having:
data List a = List a (List a) | Empty
instance Monad List where return x = List x Empty Empty >>= _ = Empty List v vs >>= f = List (f v) (vs >>= f)
is sufficient to use (in current GHC) to use: test = Empty <*> List 1 Empty Hence adding default instances + fixing the hierarchy seems to be sufficient to have backward compatibility for instance declaration.
default fmap :: Applicative f => (a -> b) -> f a -> f b f `fmap` m = pure f <*> m default pure :: Monad f => a -> f a pure = return default (<*>) :: Monad f => f (a -> b) -> f a -> f b (<*>) = liftM2 ($)
Duncan
Regards

On Sat, Sep 24, 2011 at 1:50 AM, Maciej Marcin Piechotka
On Fri, 2011-09-23 at 23:46 +0100, Duncan Coutts wrote:
On 23 September 2011 21:25, Maciej Marcin Piechotka
wrote: The problem of backward compatibility have been the main obstacle against adopting Functor f => (Pointed f =>?) => Applicative f => Monad f.
This proposition is to add following default instances[1]:
Sorry, I'm confused! The [1] link is about default superclass instances, not default signatures. As I understand it, default superclass instances are not implemented yet.
Ups. You're right.
I fully support the general aim and default superclass instances look like a very sensible way of addressing the problem. It's just not clear to me how the default signatures you're suggesting here get us closer to the goal.
Perhaps you can explain it a bit more. I suspect other people on this list don't quite get it either.
From example in link [2]. If we had:
class Functor f where fmap :: (a -> b) -> f a -> f b default fmap :: Applicative f => (a -> b) -> f a -> f b f `fmap` m = pure f <*> m (<$) :: a -> f b -> f a (<$) = fmap . const
class Functor f => Pointed f where point :: a -> f a default point :: Applicative f => a -> f a point = pure
class Pointed f => Applicative f where pure :: a -> f a default pure :: Monad f => a -> f a pure = return (<*>) :: f (a -> b) -> f a -> f b default (<*>) :: Monad f => f (a -> b) -> f a -> f b f <*> v = liftM2 ($) f v (*>) :: f a -> f b -> f b (*>) = liftA2 (const id) (<*) :: f a -> f b -> f a (<*) = liftA2 const
class Applicative f => Monad f where return :: a -> f a (>>=) :: f a -> (a -> f b) -> f b (>>) :: f a -> f b -> f b m >> k = m >>= const k
Then having:
data List a = List a (List a) | Empty
instance Monad List where return x = List x Empty Empty >>= _ = Empty List v vs >>= f = List (f v) (vs >>= f)
is sufficient to use (in current GHC) to use:
test = Empty <*> List 1 Empty
Hence adding default instances + fixing the hierarchy seems to be sufficient to have backward compatibility for instance declaration.
From what I understand (I haven't tried the extension yet) you would still need an instance declaration, even if it had no body:
instance Applicative List where instance Functor List where
to use the default methods. Antoine

On 24 September 2011 09:20, Antoine Latter
From what I understand (I haven't tried the extension yet) you would still need an instance declaration, even if it had no body:
Yes you would indeed. While I already said I liked this idea, I do see one complication: as also explained in the DefaulSuperclassInstances[1] proposal there can be multiple ways of defining fmap: default fmap :: Applicative f => (a -> b) -> f a -> f b fmap = Control.Applicative.liftA default fmap :: Traversable f => (a -> b) -> f a -> f b fmap = Data.Traversable.fmapDefault Which do we choose? I'm happy with liftA but others might disagree. With regard to [1], is there already a plan to implement them? And if so, when is it expected to be finished? If it takes some time, this might be a temporary solution. Regards, Bas [1] http://hackage.haskell.org/trac/ghc/wiki/DefaultSuperclassInstances

| With regard to [1], default superclass instances, is there already a plan to | implement them? And if so, when is it expected to be finished? | | [1] http://hackage.haskell.org/trac/ghc/wiki/DefaultSuperclassInstances It definitely won't be in 7.4 I'm afraid. One thing that would be motivating would be a list of people who actively want default superclass instances and why you want them. My own priorities for implementing stuff are much influenced by what GHC's users seem to value. I've added an "Applications" section to [1]; do add yourself and sketch how you'd use the new feature. Simon

On Sat, 2011-09-24 at 02:20 -0500, Antoine Latter wrote:
On Sat, Sep 24, 2011 at 1:50 AM, Maciej Marcin Piechotka
wrote: On Fri, 2011-09-23 at 23:46 +0100, Duncan Coutts wrote:
On 23 September 2011 21:25, Maciej Marcin Piechotka
wrote: The problem of backward compatibility have been the main obstacle against adopting Functor f => (Pointed f =>?) => Applicative f => Monad f.
This proposition is to add following default instances[1]:
Sorry, I'm confused! The [1] link is about default superclass instances, not default signatures. As I understand it, default superclass instances are not implemented yet.
Ups. You're right.
I fully support the general aim and default superclass instances look like a very sensible way of addressing the problem. It's just not clear to me how the default signatures you're suggesting here get us closer to the goal.
Perhaps you can explain it a bit more. I suspect other people on this list don't quite get it either.
From example in link [2]. If we had:
class Functor f where fmap :: (a -> b) -> f a -> f b default fmap :: Applicative f => (a -> b) -> f a -> f b f `fmap` m = pure f <*> m (<$) :: a -> f b -> f a (<$) = fmap . const
class Functor f => Pointed f where point :: a -> f a default point :: Applicative f => a -> f a point = pure
class Pointed f => Applicative f where pure :: a -> f a default pure :: Monad f => a -> f a pure = return (<*>) :: f (a -> b) -> f a -> f b default (<*>) :: Monad f => f (a -> b) -> f a -> f b f <*> v = liftM2 ($) f v (*>) :: f a -> f b -> f b (*>) = liftA2 (const id) (<*) :: f a -> f b -> f a (<*) = liftA2 const
class Applicative f => Monad f where return :: a -> f a (>>=) :: f a -> (a -> f b) -> f b (>>) :: f a -> f b -> f b m >> k = m >>= const k
Then having:
data List a = List a (List a) | Empty
instance Monad List where return x = List x Empty Empty >>= _ = Empty List v vs >>= f = List (f v) (vs >>= f)
is sufficient to use (in current GHC) to use:
test = Empty <*> List 1 Empty
Hence adding default instances + fixing the hierarchy seems to be sufficient to have backward compatibility for instance declaration.
From what I understand (I haven't tried the extension yet) you would still need an instance declaration, even if it had no body:
instance Applicative List where instance Functor List where
to use the default methods.
Antoine
Withe the current implementation in GHC you wouldn't. At least the above statement compiled fine (with full code in linked post). Regards

On 24 September 2011 12:49, Maciej Marcin Piechotka
From what I understand (I haven't tried the extension yet) you would still need an instance declaration, even if it had no body:
instance Applicative List where instance Functor List where
to use the default methods.
Antoine
Withe the current implementation in GHC you wouldn't. At least the above statement compiled fine (with full code in linked post).
Are you sure? If I run the following code in GHC: ---------------------------------------------------------------------------------- {-# LANGUAGE DefaultSignatures, NoImplicitPrelude #-} import Data.Function ((.), ($), const, id, flip) import Data.List (concatMap) class Functor f where fmap :: (a -> b) -> f a -> f b default fmap :: Applicative f => (a -> b) -> f a -> f b f `fmap` m = pure f <*> m (<$) :: a -> f b -> f a (<$) = fmap . const (<$>) :: Functor f => (a -> b) -> f a -> f b (<$>) = fmap class Functor f => Pointed f where point :: a -> f a default point :: Applicative f => a -> f a point = pure class Pointed f => Applicative f where pure :: a -> f a default pure :: Monad f => a -> f a pure = return (<*>) :: f (a -> b) -> f a -> f b default (<*>) :: Monad f => f (a -> b) -> f a -> f b f <*> v = liftM2 ($) f v (*>) :: f a -> f b -> f b (*>) = liftA2 (const id) (<*) :: f a -> f b -> f a (<*) = liftA2 const liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 f a b = f <$> a <*> b class Applicative f => Monad f where return :: a -> f a (>>=) :: f a -> (a -> f b) -> f b (>>) :: f a -> f b -> f b m >> k = m >>= const k liftM2 :: (Monad m) => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r liftM2 f m1 m2 = m1 >>= \x1 -> m2 >>= \x2 -> return (f x1 x2) instance Monad [] where return x = [x] (>>=) = flip concatMap ---------------------------------------------------------------------------------- I get the expected: No instance for (Applicative []) arising from the superclasses of an instance declaration Possible fix: add an instance declaration for (Applicative []) In the instance declaration for `Monad []' Adding these fixes it: instance Applicative [] instance Pointed [] instance Functor [] Regards, Bas

On Sat, 2011-09-24 at 13:32 +0200, Bas van Dijk wrote:
On 24 September 2011 12:49, Maciej Marcin Piechotka
wrote: From what I understand (I haven't tried the extension yet) you would still need an instance declaration, even if it had no body:
instance Applicative List where instance Functor List where
to use the default methods.
Antoine
Withe the current implementation in GHC you wouldn't. At least the above statement compiled fine (with full code in linked post).
Are you sure?
If I run the following code in GHC:
---------------------------------------------------------------------------------- {-# LANGUAGE DefaultSignatures, NoImplicitPrelude #-}
import Data.Function ((.), ($), const, id, flip) import Data.List (concatMap)
class Functor f where fmap :: (a -> b) -> f a -> f b default fmap :: Applicative f => (a -> b) -> f a -> f b f `fmap` m = pure f <*> m (<$) :: a -> f b -> f a (<$) = fmap . const
(<$>) :: Functor f => (a -> b) -> f a -> f b (<$>) = fmap
class Functor f => Pointed f where point :: a -> f a default point :: Applicative f => a -> f a point = pure
class Pointed f => Applicative f where pure :: a -> f a default pure :: Monad f => a -> f a pure = return (<*>) :: f (a -> b) -> f a -> f b default (<*>) :: Monad f => f (a -> b) -> f a -> f b f <*> v = liftM2 ($) f v (*>) :: f a -> f b -> f b (*>) = liftA2 (const id) (<*) :: f a -> f b -> f a (<*) = liftA2 const
liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 f a b = f <$> a <*> b
class Applicative f => Monad f where return :: a -> f a (>>=) :: f a -> (a -> f b) -> f b (>>) :: f a -> f b -> f b m >> k = m >>= const k
liftM2 :: (Monad m) => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r liftM2 f m1 m2 = m1 >>= \x1 -> m2 >>= \x2 -> return (f x1 x2)
instance Monad [] where return x = [x] (>>=) = flip concatMap ----------------------------------------------------------------------------------
I get the expected:
No instance for (Applicative []) arising from the superclasses of an instance declaration Possible fix: add an instance declaration for (Applicative []) In the instance declaration for `Monad []'
Adding these fixes it:
instance Applicative [] instance Pointed [] instance Functor []
Regards,
Bas
My error. I believed that complaining about missing main is the last error reported by ghc (it turns out to be one of the first). Regards

Please remember that the base library is supposed to be shared between all Haskell compilers; it is not ghc-only. If the proposal relies on an extension of the Haskell'2010 language, then your proposal must also provide equivalent functionality for all compilers that do not implement the extension (for example, selected by CPP conditional sections). Regards, Malcolm

On Fri, 2011-09-23 at 22:25 +0200, Maciej Marcin Piechotka wrote:
The problem of backward compatibility have been the main obstacle against adopting Functor f => (Pointed f =>?) => Applicative f => Monad f.
This proposition is to add following default instances[1]:
default fmap :: Applicative f => (a -> b) -> f a -> f b f `fmap` m = pure f <*> m default pure :: Monad f => a -> f a pure = return default (<*>) :: Monad f => f (a -> b) -> f a -> f b (<*>) = liftM2 ($)
The proposition is intended as step towards implementing whole hierarchy of Functor f => (Pointed f =>?) => Applicative f => Monad f[2]
Discussion period: 2 weeks
Regards
[1] It's using DefaultSuperclassInstances extentions: http://hackage.haskell.org/trac/ghc/wiki/DefaultSuperclassInstances [2] Trivial implementation is shown here: http://thread.gmane.org/gmane.comp.lang.haskell.libraries/16196
I believe that in such case the Pointed instance comes at nearly zero cost. _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
Sorry for overdue summary. From what I understend there was neither much oposition nor support for the proposal. What's the procedure in such case? Regards

On Sun, Oct 23, 2011 at 07:31:43PM +0100, Maciej Marcin Piechotka wrote:
From what I understend there was neither much oposition nor support for the proposal. What's the procedure in such case?
I've just reread the thread, and don't think there was a consensus for the change. I also think making such a core module depend on such a young extension would need strong support. Thanks Ian
participants (7)
-
Antoine Latter
-
Bas van Dijk
-
Duncan Coutts
-
Ian Lynagh
-
Maciej Marcin Piechotka
-
Malcolm Wallace
-
Simon Peyton-Jones