Proposal: Add `Generically` (or `WrappedGeneric`) newtype to GHC.Generics

Hi all, In recent years, the DefaultSignatures extension has seen popular use as a mechanism for providing derived typeclass instances via GHC.Generics. Although undeniably useful, I have always felt it is somewhat ugly: it is mutually exclusive with other, non-Generic default method implementations, and it can only be used for one Generic deriving mechanism, so implementations must choose between GHC.Generics and Data.Data. Fortunately, with the advent of DerivingVia, there is a better way: simply attach generic instances to a separate newtype, defined like newtype Generically a = Generically { unGenerically :: a } instance Generic a => C (Generically a) where ... then derive instances using DerivingVia as follows: data Foo = Bar X | Baz Y Z deriving C via Generically Foo The `Generically` name already exists for this purpose in the `generic-data` package, making it a good candidate name for a newtype in GHC.Generics (`generic-data` could simply re-export the type with suitably recent versions of `base`). An alternate name would be the more traditional `WrappedGeneric`. I don’t have much of a preference either way, but I do think the `Generically` name is cute, especially when used with DerivingVia. I believe this type should be in `base` because it is (1) clearly generally useful in the same way that similar newtypes in `base` like `WrappedMonad` are (and probably even more so), (2) extremely lightweight in terms of additional API complexity (it’s just a newtype), (3) isn’t worth depending on a separate package for, encouraging a proliferation of (possibly name-conflicting) newtypes in individual packages if it isn’t in `base`, and (4) is an opportunity to add instances based on `Generic` for classes already in `base`. Overall, it’s something that would feel right at home in GHC.Generics to me. As a final note, whichever name people prefer, it would of course make sense to provide an analogous `Generically1` or `WrappedGeneric1` type for `Generic1` (as `generic-data` does as well). Alexis

That is an absolutely *beautiful* idea. I love it to pieces. I'm not fussy
about the name, but Generically does have a nice ring to it.
On Fri, Aug 30, 2019, 2:16 PM Alexis King
Hi all,
In recent years, the DefaultSignatures extension has seen popular use as a mechanism for providing derived typeclass instances via GHC.Generics. Although undeniably useful, I have always felt it is somewhat ugly: it is mutually exclusive with other, non-Generic default method implementations, and it can only be used for one Generic deriving mechanism, so implementations must choose between GHC.Generics and Data.Data.
Fortunately, with the advent of DerivingVia, there is a better way: simply attach generic instances to a separate newtype, defined like
newtype Generically a = Generically { unGenerically :: a }
instance Generic a => C (Generically a) where ...
then derive instances using DerivingVia as follows:
data Foo = Bar X | Baz Y Z deriving C via Generically Foo
The `Generically` name already exists for this purpose in the `generic-data` package, making it a good candidate name for a newtype in GHC.Generics (`generic-data` could simply re-export the type with suitably recent versions of `base`). An alternate name would be the more traditional `WrappedGeneric`. I don’t have much of a preference either way, but I do think the `Generically` name is cute, especially when used with DerivingVia.
I believe this type should be in `base` because it is
(1) clearly generally useful in the same way that similar newtypes in `base` like `WrappedMonad` are (and probably even more so),
(2) extremely lightweight in terms of additional API complexity (it’s just a newtype),
(3) isn’t worth depending on a separate package for, encouraging a proliferation of (possibly name-conflicting) newtypes in individual packages if it isn’t in `base`, and
(4) is an opportunity to add instances based on `Generic` for classes already in `base`.
Overall, it’s something that would feel right at home in GHC.Generics to me.
As a final note, whichever name people prefer, it would of course make sense to provide an analogous `Generically1` or `WrappedGeneric1` type for `Generic1` (as `generic-data` does as well).
Alexis _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Thanks for suggesting the Alexis, I've been thinking about exactly the same
thing, albeit for other generics libraries. It would be great to have this
in GHC.Generics. I'm a +1.
I haven't really thought it out, but I wonder if
newtype GenericallyUsing a c
Also works, paving the way for other generic classes. This would let you
write
data Foo = Bar X | Baz Y Z
deriving C via Foo `GenericallyUsing` GHC.Generics.Generic
But you could also swap in SOP. This does mean instances of
GenericallyUsing would probably need Flexible instances though, and it does
complicate things.
Just throwing that out there!
Ollie
On Fri, 30 Aug 2019, 7:18 pm David Feuer,
That is an absolutely *beautiful* idea. I love it to pieces. I'm not fussy about the name, but Generically does have a nice ring to it.
On Fri, Aug 30, 2019, 2:16 PM Alexis King
wrote: Hi all,
In recent years, the DefaultSignatures extension has seen popular use as a mechanism for providing derived typeclass instances via GHC.Generics. Although undeniably useful, I have always felt it is somewhat ugly: it is mutually exclusive with other, non-Generic default method implementations, and it can only be used for one Generic deriving mechanism, so implementations must choose between GHC.Generics and Data.Data.
Fortunately, with the advent of DerivingVia, there is a better way: simply attach generic instances to a separate newtype, defined like
newtype Generically a = Generically { unGenerically :: a }
instance Generic a => C (Generically a) where ...
then derive instances using DerivingVia as follows:
data Foo = Bar X | Baz Y Z deriving C via Generically Foo
The `Generically` name already exists for this purpose in the `generic-data` package, making it a good candidate name for a newtype in GHC.Generics (`generic-data` could simply re-export the type with suitably recent versions of `base`). An alternate name would be the more traditional `WrappedGeneric`. I don’t have much of a preference either way, but I do think the `Generically` name is cute, especially when used with DerivingVia.
I believe this type should be in `base` because it is
(1) clearly generally useful in the same way that similar newtypes in `base` like `WrappedMonad` are (and probably even more so),
(2) extremely lightweight in terms of additional API complexity (it’s just a newtype),
(3) isn’t worth depending on a separate package for, encouraging a proliferation of (possibly name-conflicting) newtypes in individual packages if it isn’t in `base`, and
(4) is an opportunity to add instances based on `Generic` for classes already in `base`.
Overall, it’s something that would feel right at home in GHC.Generics to me.
As a final note, whichever name people prefer, it would of course make sense to provide an analogous `Generically1` or `WrappedGeneric1` type for `Generic1` (as `generic-data` does as well).
Alexis _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

On Aug 30, 2019, at 13:26, Oliver Charles
wrote:
I haven't really thought it out, but I wonder if
newtype GenericallyUsing a c
Also works, paving the way for other generic classes.
I don’t think this really adds anything over just having two newtypes, personally. `generics-sop` could, of course, always export its own newtype for this purpose, also named `Generically` or otherwise, and I think that would be simpler without any real disadvantages. I don’t think there are very many situations where you could be usefully polymorphic in the second type parameter of `GenericallyUsing`.

Yea, that's fair.
On Fri, 30 Aug 2019, 7:50 pm Alexis King,
On Aug 30, 2019, at 13:26, Oliver Charles
wrote: I haven't really thought it out, but I wonder if
newtype GenericallyUsing a c
Also works, paving the way for other generic classes.
I don’t think this really adds anything over just having two newtypes, personally. `generics-sop` could, of course, always export its own newtype for this purpose, also named `Generically` or otherwise, and I think that would be simpler without any real disadvantages. I don’t think there are very many situations where you could be usefully polymorphic in the second type parameter of `GenericallyUsing`.

I do have two concerns:
1. The Genetically instances for base classes will need to move to base as
well, including auxiliary classes where those are needed.
2. The Generic instance of Generically is currently a custom job. That's
really not the greatest situation in general. Is that essential for some
reason? If not, I think its Generic instance should just be derived.
On Fri, Aug 30, 2019, 2:16 PM Alexis King
Hi all,
In recent years, the DefaultSignatures extension has seen popular use as a mechanism for providing derived typeclass instances via GHC.Generics. Although undeniably useful, I have always felt it is somewhat ugly: it is mutually exclusive with other, non-Generic default method implementations, and it can only be used for one Generic deriving mechanism, so implementations must choose between GHC.Generics and Data.Data.
Fortunately, with the advent of DerivingVia, there is a better way: simply attach generic instances to a separate newtype, defined like
newtype Generically a = Generically { unGenerically :: a }
instance Generic a => C (Generically a) where ...
then derive instances using DerivingVia as follows:
data Foo = Bar X | Baz Y Z deriving C via Generically Foo
The `Generically` name already exists for this purpose in the `generic-data` package, making it a good candidate name for a newtype in GHC.Generics (`generic-data` could simply re-export the type with suitably recent versions of `base`). An alternate name would be the more traditional `WrappedGeneric`. I don’t have much of a preference either way, but I do think the `Generically` name is cute, especially when used with DerivingVia.
I believe this type should be in `base` because it is
(1) clearly generally useful in the same way that similar newtypes in `base` like `WrappedMonad` are (and probably even more so),
(2) extremely lightweight in terms of additional API complexity (it’s just a newtype),
(3) isn’t worth depending on a separate package for, encouraging a proliferation of (possibly name-conflicting) newtypes in individual packages if it isn’t in `base`, and
(4) is an opportunity to add instances based on `Generic` for classes already in `base`.
Overall, it’s something that would feel right at home in GHC.Generics to me.
As a final note, whichever name people prefer, it would of course make sense to provide an analogous `Generically1` or `WrappedGeneric1` type for `Generic1` (as `generic-data` does as well).
Alexis _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

+1
On Fri, Aug 30, 2019, 3:33 PM David Feuer
I do have two concerns:
1. The Genetically instances for base classes will need to move to base as well, including auxiliary classes where those are needed.
2. The Generic instance of Generically is currently a custom job. That's really not the greatest situation in general. Is that essential for some reason? If not, I think its Generic instance should just be derived.
On Fri, Aug 30, 2019, 2:16 PM Alexis King
wrote: Hi all,
In recent years, the DefaultSignatures extension has seen popular use as a mechanism for providing derived typeclass instances via GHC.Generics. Although undeniably useful, I have always felt it is somewhat ugly: it is mutually exclusive with other, non-Generic default method implementations, and it can only be used for one Generic deriving mechanism, so implementations must choose between GHC.Generics and Data.Data.
Fortunately, with the advent of DerivingVia, there is a better way: simply attach generic instances to a separate newtype, defined like
newtype Generically a = Generically { unGenerically :: a }
instance Generic a => C (Generically a) where ...
then derive instances using DerivingVia as follows:
data Foo = Bar X | Baz Y Z deriving C via Generically Foo
The `Generically` name already exists for this purpose in the `generic-data` package, making it a good candidate name for a newtype in GHC.Generics (`generic-data` could simply re-export the type with suitably recent versions of `base`). An alternate name would be the more traditional `WrappedGeneric`. I don’t have much of a preference either way, but I do think the `Generically` name is cute, especially when used with DerivingVia.
I believe this type should be in `base` because it is
(1) clearly generally useful in the same way that similar newtypes in `base` like `WrappedMonad` are (and probably even more so),
(2) extremely lightweight in terms of additional API complexity (it’s just a newtype),
(3) isn’t worth depending on a separate package for, encouraging a proliferation of (possibly name-conflicting) newtypes in individual packages if it isn’t in `base`, and
(4) is an opportunity to add instances based on `Generic` for classes already in `base`.
Overall, it’s something that would feel right at home in GHC.Generics to me.
As a final note, whichever name people prefer, it would of course make sense to provide an analogous `Generically1` or `WrappedGeneric1` type for `Generic1` (as `generic-data` does as well).
Alexis _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Been wanting this for a while now
On Fri, Aug 30, 2019, 4:08 PM chessai .
+1
On Fri, Aug 30, 2019, 3:33 PM David Feuer
wrote: I do have two concerns:
1. The Genetically instances for base classes will need to move to base as well, including auxiliary classes where those are needed.
2. The Generic instance of Generically is currently a custom job. That's really not the greatest situation in general. Is that essential for some reason? If not, I think its Generic instance should just be derived.
On Fri, Aug 30, 2019, 2:16 PM Alexis King
wrote: Hi all,
In recent years, the DefaultSignatures extension has seen popular use as a mechanism for providing derived typeclass instances via GHC.Generics. Although undeniably useful, I have always felt it is somewhat ugly: it is mutually exclusive with other, non-Generic default method implementations, and it can only be used for one Generic deriving mechanism, so implementations must choose between GHC.Generics and Data.Data.
Fortunately, with the advent of DerivingVia, there is a better way: simply attach generic instances to a separate newtype, defined like
newtype Generically a = Generically { unGenerically :: a }
instance Generic a => C (Generically a) where ...
then derive instances using DerivingVia as follows:
data Foo = Bar X | Baz Y Z deriving C via Generically Foo
The `Generically` name already exists for this purpose in the `generic-data` package, making it a good candidate name for a newtype in GHC.Generics (`generic-data` could simply re-export the type with suitably recent versions of `base`). An alternate name would be the more traditional `WrappedGeneric`. I don’t have much of a preference either way, but I do think the `Generically` name is cute, especially when used with DerivingVia.
I believe this type should be in `base` because it is
(1) clearly generally useful in the same way that similar newtypes in `base` like `WrappedMonad` are (and probably even more so),
(2) extremely lightweight in terms of additional API complexity (it’s just a newtype),
(3) isn’t worth depending on a separate package for, encouraging a proliferation of (possibly name-conflicting) newtypes in individual packages if it isn’t in `base`, and
(4) is an opportunity to add instances based on `Generic` for classes already in `base`.
Overall, it’s something that would feel right at home in GHC.Generics to me.
As a final note, whichever name people prefer, it would of course make sense to provide an analogous `Generically1` or `WrappedGeneric1` type for `Generic1` (as `generic-data` does as well).
Alexis _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

On Aug 30, 2019, at 14:33, David Feuer
wrote: I do have two concerns:
1. The Genetically instances for base classes will need to move to base as well, including auxiliary classes where those are needed.
Agreed. For context, the existing instances of Generically (apart from the Generic instance, discussed below) are: (Generic a, Eq (Rep a ())) => Eq (Generically a) (Generic a, Ord (Rep a ())) => Ord (Generically a) (Generic a, GBounded (Rep a)) => Bounded (Generically a) (Generic a, GEnum StandardEnum (Rep a)) => Enum (Generically a) (Generic a, GShow0 (Rep a)) => Show (Generically a) (Generic a, Semigroup (Rep a ())) => Semigroup (Generically a) (Semigroup a, Generic a, Monoid (Rep a ())) => Monoid (Generically a) I think having these in `base` is actually a good thing, since it serves as a good set of examples of how to use GHC.Generics. The current `GEnum` class might be a little too much to include in `base`, but that’s fine: it can be specialized to `GEnum StandardEnum` without breaking backwards-compatibility with `generic-data` (which can continue to provide the more sophisticated implementation).
2. The Generic instance of Generically is currently a custom job. That's really not the greatest situation in general. Is that essential for some reason? If not, I think its Generic instance should just be derived.
This is an interesting point. Again for context, the current instance is as follows: instance Generic a => Generic (Generically a) where type Rep (Generically a) = Rep a to = Generically . to from = from . unGenerically Which is to say `Generically` wrappers are invisible from the perspective of the `Generic` class. Personally, I think this instance makes sense: think of every instance of some class `C` on `Generically a` is supposed to provide an instance of `C a` in terms of `Generic a`, and that is exactly what `Generic (Generically a)` does. However, it’s obviously a useless instance, since it’s just the identity function on an existing `Generic a` dictionary. In any case, I think it’s harmless, but I can understand why you might think it’s sketchy.

I'm okay with moving those things into base. I'm even okay with doing some
fancy ad hoc thing with Enum (Enum is a bad joke anyway). But the Generic
instance gives me the heeby jeebies. Will it hurt anyone to just derive
Generic there? (And both Generic and Generic1 for Generically1?). I'd
rather not just omit it, but I think that would be better than this.
On Fri, Aug 30, 2019, 4:11 PM Alexis King
On Aug 30, 2019, at 14:33, David Feuer
wrote: I do have two concerns:
1. The Genetically instances for base classes will need to move to base as well, including auxiliary classes where those are needed.
Agreed. For context, the existing instances of Generically (apart from the Generic instance, discussed below) are:
(Generic a, Eq (Rep a ())) => Eq (Generically a) (Generic a, Ord (Rep a ())) => Ord (Generically a) (Generic a, GBounded (Rep a)) => Bounded (Generically a) (Generic a, GEnum StandardEnum (Rep a)) => Enum (Generically a) (Generic a, GShow0 (Rep a)) => Show (Generically a) (Generic a, Semigroup (Rep a ())) => Semigroup (Generically a) (Semigroup a, Generic a, Monoid (Rep a ())) => Monoid (Generically a)
I think having these in `base` is actually a good thing, since it serves as a good set of examples of how to use GHC.Generics. The current `GEnum` class might be a little too much to include in `base`, but that’s fine: it can be specialized to `GEnum StandardEnum` without breaking backwards-compatibility with `generic-data` (which can continue to provide the more sophisticated implementation).
2. The Generic instance of Generically is currently a custom job. That's really not the greatest situation in general. Is that essential for some reason? If not, I think its Generic instance should just be derived.
This is an interesting point. Again for context, the current instance is as follows:
instance Generic a => Generic (Generically a) where type Rep (Generically a) = Rep a to = Generically . to from = from . unGenerically
Which is to say `Generically` wrappers are invisible from the perspective of the `Generic` class.
Personally, I think this instance makes sense: think of every instance of some class `C` on `Generically a` is supposed to provide an instance of `C a` in terms of `Generic a`, and that is exactly what `Generic (Generically a)` does. However, it’s obviously a useless instance, since it’s just the identity function on an existing `Generic a` dictionary. In any case, I think it’s harmless, but I can understand why you might think it’s sketchy.

I don’t think a derived `Generic` instance makes any more sense for `Generically` than a derived `Show` instance does. What would be the purpose of such an instance? Again, `instance C (Generically a)` is morally a function on dictionaries of type `Generic a -> C a`, and every instance on `Generically` should have that relationship. The existing `Generic` instance does, but a derived `Generic` instance would not. If you want to leave that instance out, that’s fine with me; I highly doubt anyone would miss it. As I said before, it’s totally useless. But a derived `Generic` instance seems to have no purpose and would be inconsistent with the rules the other instances obey, so it seems strictly worse than no instance to me.
On Aug 30, 2019, at 16:46, David Feuer
wrote: I'm okay with moving those things into base. I'm even okay with doing some fancy ad hoc thing with Enum (Enum is a bad joke anyway). But the Generic instance gives me the heeby jeebies. Will it hurt anyone to just derive Generic there? (And both Generic and Generic1 for Generically1?). I'd rather not just omit it, but I think that would be better than this.
On Fri, Aug 30, 2019, 4:11 PM Alexis King
mailto:lexi.lambda@gmail.com> wrote: On Aug 30, 2019, at 14:33, David Feuer
mailto:david.feuer@gmail.com> wrote: I do have two concerns:
1. The Genetically instances for base classes will need to move to base as well, including auxiliary classes where those are needed.
Agreed. For context, the existing instances of Generically (apart from the Generic instance, discussed below) are:
(Generic a, Eq (Rep a ())) => Eq (Generically a) (Generic a, Ord (Rep a ())) => Ord (Generically a) (Generic a, GBounded (Rep a)) => Bounded (Generically a) (Generic a, GEnum StandardEnum (Rep a)) => Enum (Generically a) (Generic a, GShow0 (Rep a)) => Show (Generically a) (Generic a, Semigroup (Rep a ())) => Semigroup (Generically a) (Semigroup a, Generic a, Monoid (Rep a ())) => Monoid (Generically a)
I think having these in `base` is actually a good thing, since it serves as a good set of examples of how to use GHC.Generics. The current `GEnum` class might be a little too much to include in `base`, but that’s fine: it can be specialized to `GEnum StandardEnum` without breaking backwards-compatibility with `generic-data` (which can continue to provide the more sophisticated implementation).
2. The Generic instance of Generically is currently a custom job. That's really not the greatest situation in general. Is that essential for some reason? If not, I think its Generic instance should just be derived.
This is an interesting point. Again for context, the current instance is as follows:
instance Generic a => Generic (Generically a) where type Rep (Generically a) = Rep a to = Generically . to from = from . unGenerically
Which is to say `Generically` wrappers are invisible from the perspective of the `Generic` class.
Personally, I think this instance makes sense: think of every instance of some class `C` on `Generically a` is supposed to provide an instance of `C a` in terms of `Generic a`, and that is exactly what `Generic (Generically a)` does. However, it’s obviously a useless instance, since it’s just the identity function on an existing `Generic a` dictionary. In any case, I think it’s harmless, but I can understand why you might think it’s sketchy.

On Aug 30, 2019, at 17:26, Alexis King
wrote: If you want to leave that instance out, that’s fine with me; I highly doubt anyone would miss it. As I said before, it’s totally useless.
Actually, I take this back. It’s not totally useless, just unlikely to be useful (and ultimately inessential). It’s theoretically useful if you have some function like foo :: (Show a, Generic a) => a -> Foo and want to use the generic version of the `Show` instance, but for some reason don’t want to actually define that instance on your type. You can write `foo (Generically x)`, and it will work out. That wouldn’t work if `Generic (Generically a)` were the derived instance. On the other hand, you could always get the same behavior in a more flexible way by just defining a separate newtype and deriving the relevant instances as desired, like this: newtype GenericallyShowable a = GenericallyShowable a deriving newtype (Generic) deriving (Show) via Generically a So the instance isn’t necessary by any means, nor does it seem particularly likely to be useful in practice, but it doesn’t seem impossible that it ever could be. My vote is to keep it; I don’t see the harm.

It sounds like we can probably agree not to include the instance for now.
But I don't want to just go with my gut feeling, so here's a concrete
reason:
Generically isn't *just* a DerivingVia target: it's also a perfectly
reasonable newtype in its own right. Consider something like
CoercibleUtils.Newtype [*]. If you try to work `under Generically` with
your instance, then the type checker won't let you. That's rather sad, I
think, because it seems like a perfectly sensible thing to do.
[*]
https://github.com/sjakobi/coercible-utils/blob/072c60837059aaaac47628a1822c...
On Fri, Aug 30, 2019, 8:26 PM Alexis King
On Aug 30, 2019, at 17:26, Alexis King
wrote: If you want to leave that instance out, that’s fine with me; I highly doubt anyone would miss it. As I said before, it’s totally useless.
Actually, I take this back. It’s not totally useless, just unlikely to be useful (and ultimately inessential). It’s theoretically useful if you have some function like
foo :: (Show a, Generic a) => a -> Foo
and want to use the generic version of the `Show` instance, but for some reason don’t want to actually define that instance on your type. You can write `foo (Generically x)`, and it will work out. That wouldn’t work if `Generic (Generically a)` were the derived instance.
On the other hand, you could always get the same behavior in a more flexible way by just defining a separate newtype and deriving the relevant instances as desired, like this:
newtype GenericallyShowable a = GenericallyShowable a deriving newtype (Generic) deriving (Show) via Generically a
So the instance isn’t necessary by any means, nor does it seem particularly likely to be useful in practice, but it doesn’t seem impossible that it ever could be. My vote is to keep it; I don’t see the harm.

+1, this is a great idea
On Sat, Aug 31, 2019 at 2:36 AM David Feuer
It sounds like we can probably agree not to include the instance for now. But I don't want to just go with my gut feeling, so here's a concrete reason:
Generically isn't *just* a DerivingVia target: it's also a perfectly reasonable newtype in its own right. Consider something like CoercibleUtils.Newtype [*]. If you try to work `under Generically` with your instance, then the type checker won't let you. That's rather sad, I think, because it seems like a perfectly sensible thing to do.
[*] https://github.com/sjakobi/coercible-utils/blob/072c60837059aaaac47628a1822c...
On Fri, Aug 30, 2019, 8:26 PM Alexis King
wrote: On Aug 30, 2019, at 17:26, Alexis King
wrote: If you want to leave that instance out, that’s fine with me; I highly doubt anyone would miss it. As I said before, it’s totally useless.
Actually, I take this back. It’s not totally useless, just unlikely to be useful (and ultimately inessential). It’s theoretically useful if you have some function like
foo :: (Show a, Generic a) => a -> Foo
and want to use the generic version of the `Show` instance, but for some reason don’t want to actually define that instance on your type. You can write `foo (Generically x)`, and it will work out. That wouldn’t work if `Generic (Generically a)` were the derived instance.
On the other hand, you could always get the same behavior in a more flexible way by just defining a separate newtype and deriving the relevant instances as desired, like this:
newtype GenericallyShowable a = GenericallyShowable a deriving newtype (Generic) deriving (Show) via Generically a
So the instance isn’t necessary by any means, nor does it seem particularly likely to be useful in practice, but it doesn’t seem impossible that it ever could be. My vote is to keep it; I don’t see the harm.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

+1
This sounds very useful. I also thought about having this `newtype` in the
past and there were even some posts on Reddit about such feature.
Basically, after this change, we can start recommending using
`Generically` + `DerivingVia` instead of `DefaultSignatures`. It always
bothered me that you can have only one default signature and for some
reasons it's implemented for generics in almost every package. It just
seems too arbitrary and ad-hoc to me. `newtype`s feel like a more natural
solution. Instead of relying on whatever `default-signature` provides you
can explicitly specify your deriving strategy.
On Fri, Aug 30, 2019 at 9:16 PM Alexis King
Hi all,
In recent years, the DefaultSignatures extension has seen popular use as a mechanism for providing derived typeclass instances via GHC.Generics. Although undeniably useful, I have always felt it is somewhat ugly: it is mutually exclusive with other, non-Generic default method implementations, and it can only be used for one Generic deriving mechanism, so implementations must choose between GHC.Generics and Data.Data.
Fortunately, with the advent of DerivingVia, there is a better way: simply attach generic instances to a separate newtype, defined like
newtype Generically a = Generically { unGenerically :: a }
instance Generic a => C (Generically a) where ...
then derive instances using DerivingVia as follows:
data Foo = Bar X | Baz Y Z deriving C via Generically Foo
The `Generically` name already exists for this purpose in the `generic-data` package, making it a good candidate name for a newtype in GHC.Generics (`generic-data` could simply re-export the type with suitably recent versions of `base`). An alternate name would be the more traditional `WrappedGeneric`. I don’t have much of a preference either way, but I do think the `Generically` name is cute, especially when used with DerivingVia.
I believe this type should be in `base` because it is
(1) clearly generally useful in the same way that similar newtypes in `base` like `WrappedMonad` are (and probably even more so),
(2) extremely lightweight in terms of additional API complexity (it’s just a newtype),
(3) isn’t worth depending on a separate package for, encouraging a proliferation of (possibly name-conflicting) newtypes in individual packages if it isn’t in `base`, and
(4) is an opportunity to add instances based on `Generic` for classes already in `base`.
Overall, it’s something that would feel right at home in GHC.Generics to me.
As a final note, whichever name people prefer, it would of course make sense to provide an analogous `Generically1` or `WrappedGeneric1` type for `Generic1` (as `generic-data` does as well).
Alexis _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Also, default signatures look dreadful in haddocks.
On Sun, Sep 1, 2019, 1:56 AM Dmitrii Kovanikov
+1
This sounds very useful. I also thought about having this `newtype` in the past and there were even some posts on Reddit about such feature.
Basically, after this change, we can start recommending using `Generically` + `DerivingVia` instead of `DefaultSignatures`. It always bothered me that you can have only one default signature and for some reasons it's implemented for generics in almost every package. It just seems too arbitrary and ad-hoc to me. `newtype`s feel like a more natural solution. Instead of relying on whatever `default-signature` provides you can explicitly specify your deriving strategy.
On Fri, Aug 30, 2019 at 9:16 PM Alexis King
wrote: Hi all,
In recent years, the DefaultSignatures extension has seen popular use as a mechanism for providing derived typeclass instances via GHC.Generics. Although undeniably useful, I have always felt it is somewhat ugly: it is mutually exclusive with other, non-Generic default method implementations, and it can only be used for one Generic deriving mechanism, so implementations must choose between GHC.Generics and Data.Data.
Fortunately, with the advent of DerivingVia, there is a better way: simply attach generic instances to a separate newtype, defined like
newtype Generically a = Generically { unGenerically :: a }
instance Generic a => C (Generically a) where ...
then derive instances using DerivingVia as follows:
data Foo = Bar X | Baz Y Z deriving C via Generically Foo
The `Generically` name already exists for this purpose in the `generic-data` package, making it a good candidate name for a newtype in GHC.Generics (`generic-data` could simply re-export the type with suitably recent versions of `base`). An alternate name would be the more traditional `WrappedGeneric`. I don’t have much of a preference either way, but I do think the `Generically` name is cute, especially when used with DerivingVia.
I believe this type should be in `base` because it is
(1) clearly generally useful in the same way that similar newtypes in `base` like `WrappedMonad` are (and probably even more so),
(2) extremely lightweight in terms of additional API complexity (it’s just a newtype),
(3) isn’t worth depending on a separate package for, encouraging a proliferation of (possibly name-conflicting) newtypes in individual packages if it isn’t in `base`, and
(4) is an opportunity to add instances based on `Generic` for classes already in `base`.
Overall, it’s something that would feel right at home in GHC.Generics to me.
As a final note, whichever name people prefer, it would of course make sense to provide an analogous `Generically1` or `WrappedGeneric1` type for `Generic1` (as `generic-data` does as well).
Alexis _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Note, that many Generic-derived instances for newtypes are equivalent with GND instance. Generic mechanism is powerful enough to notice newtype special case.
On 1 Sep 2019, at 8.56, Dmitrii Kovanikov
wrote: +1
This sounds very useful. I also thought about having this `newtype` in the past and there were even some posts on Reddit about such feature.
Basically, after this change, we can start recommending using `Generically` + `DerivingVia` instead of `DefaultSignatures`. It always bothered me that you can have only one default signature and for some reasons it's implemented for generics in almost every package. It just seems too arbitrary and ad-hoc to me. `newtype`s feel like a more natural solution. Instead of relying on whatever `default-signature` provides you can explicitly specify your deriving strategy.
On Fri, Aug 30, 2019 at 9:16 PM Alexis King
wrote: Hi all, In recent years, the DefaultSignatures extension has seen popular use as a mechanism for providing derived typeclass instances via GHC.Generics. Although undeniably useful, I have always felt it is somewhat ugly: it is mutually exclusive with other, non-Generic default method implementations, and it can only be used for one Generic deriving mechanism, so implementations must choose between GHC.Generics and Data.Data.
Fortunately, with the advent of DerivingVia, there is a better way: simply attach generic instances to a separate newtype, defined like
newtype Generically a = Generically { unGenerically :: a }
instance Generic a => C (Generically a) where ...
then derive instances using DerivingVia as follows:
data Foo = Bar X | Baz Y Z deriving C via Generically Foo
The `Generically` name already exists for this purpose in the `generic-data` package, making it a good candidate name for a newtype in GHC.Generics (`generic-data` could simply re-export the type with suitably recent versions of `base`). An alternate name would be the more traditional `WrappedGeneric`. I don’t have much of a preference either way, but I do think the `Generically` name is cute, especially when used with DerivingVia.
I believe this type should be in `base` because it is
(1) clearly generally useful in the same way that similar newtypes in `base` like `WrappedMonad` are (and probably even more so),
(2) extremely lightweight in terms of additional API complexity (it’s just a newtype),
(3) isn’t worth depending on a separate package for, encouraging a proliferation of (possibly name-conflicting) newtypes in individual packages if it isn’t in `base`, and
(4) is an opportunity to add instances based on `Generic` for classes already in `base`.
Overall, it’s something that would feel right at home in GHC.Generics to me.
As a final note, whichever name people prefer, it would of course make sense to provide an analogous `Generically1` or `WrappedGeneric1` type for `Generic1` (as `generic-data` does as well).
Alexis _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

As just one more data point, Rob Rix from the GitHub semantic code team has pointed out to me that their `semantic` library also includes a `Generically1` type, defined here: https://github.com/github/semantic/blob/8c0041f1ec5a3ee9f3d0294c35220bfde209... (They call it `Generically`, but it’s actually equivalent to the `Generically1` type from `generic-data` and serves the same purpose.)
participants (7)
-
Alexis King
-
chessai .
-
David Feuer
-
Dmitrii Kovanikov
-
Nathan Bouscal
-
Oleg Grenrus
-
Oliver Charles