Narrower (per-method) GND

There are some situations where we may want to use GND to derive some class methods when it's not applicable to others. For example, some people would very much like to add a join method to Monad, but doing so would prevent GND from working for Monad. Similarly, the distribute method of Data.Distributive.Distributive is incompatible with GND. In each of these cases, a perfectly valid, and efficient, way to derive the class would be to use the GND mechanism to derive the methods it works with and the default method definitions for the rest. To cover these cases, I think it would be nice to allow a method declaration to give a default definition intended to be used for GND. This may or may not be the same as the usual default. Some classes can support GND for some methods, but using defaults for the others would give poor implementations. To cover this case, I think it would be nice to add per-method GND-deriving syntax. This could look something like instance C T where deriving f g = ....

Hi, just responding to this one aspect: Am Sonntag, den 08.01.2017, 21:16 -0500 schrieb David Feuer:
but using defaults for the others would give poor implementations. To cover this case, I think it would be nice to add per-method GND-deriving syntax. This could look something like
instance C T where deriving f g = ....
Assuming newtype T = MkT S You can achieve this using instance C T where f = coerce (f @F) g = .... (which is precisely what GND does), so I don’t think any new syntax is needed here. Greetings, Joachim -- Joachim “nomeata” Breitner mail@joachim-breitner.de • https://www.joachim-breitner.de/ XMPP: nomeata@joachim-breitner.de • OpenPGP-Key: 0xF0FBF51F Debian Developer: nomeata@debian.org

You *can* do this, but it's often not so concise. When the type constructor
has parameters, you need to pin them down using ScopedTypeVariables. So you
end up needing to give a signature for the method type in order to bring
into scope variables you then use in the argument to coerce. If you have
newtype Foo f a = Foo (Foo f a)
then you may need
instance Bar f => Bar (Foo f) where
bah = coerce (bah @ f @ a)
:: forall a . C a => ...
to pin down the C instance.
If you don't want to use explicit type application (e.g., you're using a
library that does not claim to have stable type argument order), things get
even more verbose.
On Jan 8, 2017 11:32 PM, "Joachim Breitner"
Hi,
just responding to this one aspect:
Am Sonntag, den 08.01.2017, 21:16 -0500 schrieb David Feuer:
but using defaults for the others would give poor implementations. To cover this case, I think it would be nice to add per-method GND-deriving syntax. This could look something like
instance C T where deriving f g = ....
Assuming newtype T = MkT S
You can achieve this using
instance C T where f = coerce (f @F) g = ....
(which is precisely what GND does), so I don’t think any new syntax is needed here.
Greetings, Joachim
-- Joachim “nomeata” Breitner mail@joachim-breitner.de • https://www.joachim-breitner.de/ XMPP: nomeata@joachim-breitner.de • OpenPGP-Key: 0xF0FBF51F Debian Developer: nomeata@debian.org _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users

I agree with David that using explicit `coerce`s can be quite verbose and may need ScopedTypeVariables and InstanceSigs. But visible type application should always work, because class methods always have a fixed type argument order. Regardless, requiring users to do all this for GND on Monad would be frustrating. Actually, I just had an insight about this: there is no reason to use one deriving strategy for all methods in an instance. I can think of 4 ways to fill in the implementation of a class method in an instance: 1. Explicit, hand-written implementation 2. Defaulting to the implementation written in the class (or `error "undefined method"` in the absence of a default. This is essentially the default default.) 3. Stock implementation provided by GHC 4. Coerce Ways 2, 3, and 4 all have extra restrictions: Way 2 might have extra type constraints due to a `default` signature. Way 3 restricts the choice of class and type. Way 4 works only on newtypes and then imposes role restrictions on the method's type. GHC provides a `deriving` mechanism so that you can request Way 2 (`default`), 3 (`stock`), or 4 (`newtype`) to fill in every method in a class. But there's no need to provide this feature at such a course granularity. What about:
newtype N a = MkN (Foo a) instance Blah a => C (N a) where meth1 = ... deriving default meth2 -- a bit silly really, as you can just leave meth2 out deriving stock meth3 -- also silly, as C isn't a stock class, but you get the idea deriving newtype meth4
We could also imagine
deriving newtype instance Blah a => Monad (N a) where deriving default join -- not so silly anymore!
This syntax allows a `where` clause on standalone deriving allowing you to override the overall `deriving` behavior on a per-method basis. I actually quite like this extension... Richard
On Jan 8, 2017, at 11:54 PM, David Feuer
wrote: You *can* do this, but it's often not so concise. When the type constructor has parameters, you need to pin them down using ScopedTypeVariables. So you end up needing to give a signature for the method type in order to bring into scope variables you then use in the argument to coerce. If you have
newtype Foo f a = Foo (Foo f a)
then you may need
instance Bar f => Bar (Foo f) where bah = coerce (bah @ f @ a) :: forall a . C a => ...
to pin down the C instance.
If you don't want to use explicit type application (e.g., you're using a library that does not claim to have stable type argument order), things get even more verbose.
On Jan 8, 2017 11:32 PM, "Joachim Breitner"
mailto:mail@joachim-breitner.de> wrote: Hi, just responding to this one aspect:
Am Sonntag, den 08.01.2017, 21:16 -0500 schrieb David Feuer:
but using defaults for the others would give poor implementations. To cover this case, I think it would be nice to add per-method GND-deriving syntax. This could look something like
instance C T where deriving f g = ....
Assuming newtype T = MkT S
You can achieve this using
instance C T where f = coerce (f @F) g = ....
(which is precisely what GND does), so I don’t think any new syntax is needed here.
Greetings, Joachim
-- Joachim “nomeata” Breitner mail@joachim-breitner.de mailto:mail@joachim-breitner.de • https://www.joachim-breitner.de/ https://www.joachim-breitner.de/ XMPP: nomeata@joachim-breitner.de mailto:nomeata@joachim-breitner.de • OpenPGP-Key: 0xF0FBF51F Debian Developer: nomeata@debian.org mailto:nomeata@debian.org _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org mailto:Glasgow-haskell-users@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users

Richard — your idea is really interesting. How would the dreaded role restriction have to be modified to detect and allow this sort of granularity? —g On January 9, 2017 at 1:34:17 PM, Richard Eisenberg (rae@cs.brynmawr.edu) wrote:
I agree with David that using explicit `coerce`s can be quite verbose and may need ScopedTypeVariables and InstanceSigs. But visible type application should always work, because class methods always have a fixed type argument order. Regardless, requiring users to do all this for GND on Monad would be frustrating.
Actually, I just had an insight about this: there is no reason to use one deriving strategy for all methods in an instance. I can think of 4 ways to fill in the implementation of a class method in an instance:
1. Explicit, hand-written implementation 2. Defaulting to the implementation written in the class (or `error "undefined method"` in the absence of a default. This is essentially the default default.) 3. Stock implementation provided by GHC 4. Coerce
Ways 2, 3, and 4 all have extra restrictions: Way 2 might have extra type constraints due to a `default` signature. Way 3 restricts the choice of class and type. Way 4 works only on newtypes and then imposes role restrictions on the method's type.
GHC provides a `deriving` mechanism so that you can request Way 2 (`default`), 3 (`stock`), or 4 (`newtype`) to fill in every method in a class. But there's no need to provide this feature at such a course granularity. What about:
newtype N a = MkN (Foo a) instance Blah a => C (N a) where meth1 = ... deriving default meth2 -- a bit silly really, as you can just leave meth2 out deriving stock meth3 -- also silly, as C isn't a stock class, but you get the idea deriving newtype meth4
We could also imagine
deriving newtype instance Blah a => Monad (N a) where deriving default join -- not so silly anymore!
This syntax allows a `where` clause on standalone deriving allowing you to override the overall `deriving` behavior on a per-method basis.
I actually quite like this extension...
Richard
On Jan 8, 2017, at 11:54 PM, David Feuer wrote:
You *can* do this, but it's often not so concise. When the type constructor has parameters, you need to pin them down using ScopedTypeVariables. So you end up needing to give a signature for the method type in order to bring into scope variables you then use in the argument to coerce. If you have
newtype Foo f a = Foo (Foo f a)
then you may need
instance Bar f => Bar (Foo f) where bah = coerce (bah @ f @ a) :: forall a . C a => ...
to pin down the C instance.
If you don't want to use explicit type application (e.g., you're using a library that does not claim to have stable type argument order), things get even more verbose.
On Jan 8, 2017 11:32 PM, "Joachim Breitner" > wrote: Hi,
just responding to this one aspect:
Am Sonntag, den 08.01.2017, 21:16 -0500 schrieb David Feuer:
but using defaults for the others would give poor implementations. To cover this case, I think it would be nice to add per-method GND-deriving syntax. This could look something like
instance C T where deriving f g = ....
Assuming newtype T = MkT S
You can achieve this using
instance C T where f = coerce (f @F) g = ....
(which is precisely what GND does), so I don’t think any new syntax is needed here.
Greetings, Joachim
-- Joachim “nomeata” Breitner mail@joachim-breitner.de • https://www.joachim-breitner.de/
XMPP: nomeata@joachim-breitner.de • OpenPGP-Key: 0xF0FBF51F Debian Developer: nomeata@debian.org _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users

On Jan 9, 2017, at 1:57 PM, Gershom B
wrote: Richard — your idea is really interesting. How would the dreaded role restriction have to be modified to detect and allow this sort of granularity?
It wouldn't. The role restriction is purely on a method-by-method basis. (Right now, the role restriction is not enforced at the class level -- you just get a type error on the method that GND produces. See below.) So this new feature wouldn't interact with roles directly, at all. Also, looking back through these emails, I realize my "insight" was really just the logical conclusion of David's original suggestion. Not much of an insight really, just some concrete syntax. Richard Example of bad GND:
class Functor m => M m where join :: m (m a) -> m a
newtype ReaderT r m a = ReaderT { runReaderT :: r -> m a }
instance Functor m => Functor (ReaderT r m) where fmap f x = ReaderT $ \r -> fmap f (runReaderT x r)
instance M m => M (ReaderT r m) where join x = ReaderT $ \r -> join (fmap (($ r) . runReaderT) (runReaderT x r))
newtype N m a = MkN (ReaderT Int m a) deriving (Functor, M)
This produces
• Couldn't match representation of type ‘m (N m a)’ with that of ‘m (ReaderT Int m a)’ arising from the coercion of the method ‘join’ from type ‘forall a. ReaderT Int m (ReaderT Int m a) -> ReaderT Int m a’ to type ‘forall a. N m (N m a) -> N m a’ NB: We cannot know what roles the parameters to ‘m’ have; we must assume that the role is nominal • When deriving the instance for (M (N m))
in GHC 8.0.1.
—g
On January 9, 2017 at 1:34:17 PM, Richard Eisenberg (rae@cs.brynmawr.edu) wrote:
I agree with David that using explicit `coerce`s can be quite verbose and may need ScopedTypeVariables and InstanceSigs. But visible type application should always work, because class methods always have a fixed type argument order. Regardless, requiring users to do all this for GND on Monad would be frustrating.
Actually, I just had an insight about this: there is no reason to use one deriving strategy for all methods in an instance. I can think of 4 ways to fill in the implementation of a class method in an instance:
1. Explicit, hand-written implementation 2. Defaulting to the implementation written in the class (or `error "undefined method"` in the absence of a default. This is essentially the default default.) 3. Stock implementation provided by GHC 4. Coerce
Ways 2, 3, and 4 all have extra restrictions: Way 2 might have extra type constraints due to a `default` signature. Way 3 restricts the choice of class and type. Way 4 works only on newtypes and then imposes role restrictions on the method's type.
GHC provides a `deriving` mechanism so that you can request Way 2 (`default`), 3 (`stock`), or 4 (`newtype`) to fill in every method in a class. But there's no need to provide this feature at such a course granularity. What about:
newtype N a = MkN (Foo a) instance Blah a => C (N a) where meth1 = ... deriving default meth2 -- a bit silly really, as you can just leave meth2 out deriving stock meth3 -- also silly, as C isn't a stock class, but you get the idea deriving newtype meth4
We could also imagine
deriving newtype instance Blah a => Monad (N a) where deriving default join -- not so silly anymore!
This syntax allows a `where` clause on standalone deriving allowing you to override the overall `deriving` behavior on a per-method basis.
I actually quite like this extension...
Richard
On Jan 8, 2017, at 11:54 PM, David Feuer wrote:
You *can* do this, but it's often not so concise. When the type constructor has parameters, you need to pin them down using ScopedTypeVariables. So you end up needing to give a signature for the method type in order to bring into scope variables you then use in the argument to coerce. If you have
newtype Foo f a = Foo (Foo f a)
then you may need
instance Bar f => Bar (Foo f) where bah = coerce (bah @ f @ a) :: forall a . C a => ...
to pin down the C instance.
If you don't want to use explicit type application (e.g., you're using a library that does not claim to have stable type argument order), things get even more verbose.
On Jan 8, 2017 11:32 PM, "Joachim Breitner" > wrote: Hi,
just responding to this one aspect:
Am Sonntag, den 08.01.2017, 21:16 -0500 schrieb David Feuer:
but using defaults for the others would give poor implementations. To cover this case, I think it would be nice to add per-method GND-deriving syntax. This could look something like
instance C T where deriving f g = ....
Assuming newtype T = MkT S
You can achieve this using
instance C T where f = coerce (f @F) g = ....
(which is precisely what GND does), so I don’t think any new syntax is needed here.
Greetings, Joachim
-- Joachim “nomeata” Breitner mail@joachim-breitner.de • https://www.joachim-breitner.de/
XMPP: nomeata@joachim-breitner.de • OpenPGP-Key: 0xF0FBF51F Debian Developer: nomeata@debian.org _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users

On Mon, Jan 9, 2017 at 1:32 PM, Richard Eisenberg
2. Defaulting to the implementation written in the class (or `error "undefined method"` in the absence of a default. This is essentially the default default.)
I want to be able to specify that a certain default definition is good enough not to worry about. For example (with horribly bad syntax), class Applicative m => Monad m where (>>=) :: m a -> (a -> m b) -> m b m >>= f = join (f <$> m) -- plain old default join :: m (m a) -> m a good_enough_default join = (>>= id) This would allow users to just write newtype Foo a = Foo ... deriving Monad which would then be equivalent (using the notation you came up with) to instance Monad Foo where deriving newtype (>>=) David Feuer

On Mon, Jan 9, 2017 at 5:11 PM, David Feuer
On Mon, Jan 9, 2017 at 1:32 PM, Richard Eisenberg
wrote: 2. Defaulting to the implementation written in the class (or `error "undefined method"` in the absence of a default. This is essentially the default default.)
I want to be able to specify that a certain default definition is good enough not to worry about.
Is this the same as the purpose of the MINIMAL pragma? http://ghc.readthedocs.io/en/latest/glasgow_exts.html#minimal-pragma Imagine GND provides implementations for those methods whose types are amenable to `coerce`ion and leaves the other methods without definitions. Then, taking into account the MINIMAL pragma, GHC either does or does not produce a warning/error about missing class methods, maybe customized to mention the failure to `coerce` a method in GND. Would that be adequate? Regards, Reid Barton

No, I don't think that would be adequate, but maybe there's a way to work
that in. It's inadequate because MINIMAL doesn't carry any assertion of
efficiency. If I indicate I want a class derived by GND, and it works, then
I expect its implementation to be, at worst, very very slightly slower than
the underlying implementation. If the class author doesn't make such a
claim, I want users to have to be explicit about the methods derived by GND.
On Jan 12, 2017 8:01 AM, "Reid Barton"
On Mon, Jan 9, 2017 at 5:11 PM, David Feuer
wrote: On Mon, Jan 9, 2017 at 1:32 PM, Richard Eisenberg
wrote: 2. Defaulting to the implementation written in the class (or `error "undefined method"` in the absence of a default. This is essentially the default default.)
I want to be able to specify that a certain default definition is good enough not to worry about.
Is this the same as the purpose of the MINIMAL pragma? http://ghc.readthedocs.io/en/latest/glasgow_exts.html#minimal-pragma
Imagine GND provides implementations for those methods whose types are amenable to `coerce`ion and leaves the other methods without definitions. Then, taking into account the MINIMAL pragma, GHC either does or does not produce a warning/error about missing class methods, maybe customized to mention the failure to `coerce` a method in GND. Would that be adequate?
Regards, Reid Barton

On Mon, Jan 9, 2017 at 1:32 PM, Richard Eisenberg
I agree with David that using explicit `coerce`s can be quite verbose and may need ScopedTypeVariables and InstanceSigs. But visible type application should always work, because class methods always have a fixed type argument order.
Oh, I missed this bit. That claim is not quite true. I could have something like class Two f where two :: (Integral a, Num b) => proxy (f a b) -> String Unless the package defining this class promises not to, its maintainer could later change that to two :: forall b a proxy . (Integral a, Num b) => proxy (f a b) -> String which could silently break code. Or change the position of the proxy argument and loudly break code.
participants (5)
-
David Feuer
-
Gershom B
-
Joachim Breitner
-
Reid Barton
-
Richard Eisenberg