haskell / core-libraries-committee

95 stars 16 forks source link

Proposal: Relax instances for Functor combinators; put superclasses on <class>1 to make less-breaking #10

Closed Ericson2314 closed 2 years ago

Ericson2314 commented 3 years ago

Implementation https://gitlab.haskell.org/ghc/ghc/-/merge_requests/4727

The first change makes the Eq, Ord, Show, and Read instances for Sum, Product, and Compose match those for :+:, :*:, and :.:. These have the proper flexible contexts that are exactly what the instance needs:

For example, instead of

instance (Eq1 f, Eq1 g, Eq a) => Eq (Compose f g a) where
  (==) = eq1

we do

deriving instance Eq (f (g a)) => Eq (Compose f g a)

But, that change alone is rather breaking, because until now Eq (f a) and Eq1 f (and respectively the other classes and their *1 equivalents too) are incomparable constraints. This has always been an annoyance of working with the *1 classes, and now it would rear it's head one last time as an pesky migration.

Instead, we give the *1 classes superclasses, like so:

(forall a. Eq a => Eq (f a)) => Eq1 f

along with some laws that canonicity is preserved, like:

liftEq (==) = (==)

and likewise for *2 classes

(forall a. Eq a => Eq1 (f a)) => Eq2 f

along with some laws that canonicity is preserved, like:

liftEq2 (==) = liftEq1

The *1 classes also have default methods using the *2 classes where possible.

What this means, as explained in the docs in my implementation, is that *1 classes really are generations of the regular classes, indicating that the methods can be split into a canonical lifting combined with a canonical inner, with the super class "witnessing" the laws[1] in a fashion.

Circling back to the pragmatics of migrating, note that the superclass means evidence for the old Sum, Product, and Compose instances is (more than) sufficient, so breakage is less likely --- as long no instances are "missing", existing polymorphic code will continue to work.

Breakage can occur when a datatype implements the *1 class but not the corresponding regular class, but this is almost certainly an oversight. For example, containers made that mistake for Tree and Ord, which I fixed in https://github.com/haskell/containers/pull/761, but fixing the issue by adding Ord1 was extremely uncontroversial.


[1]: In fact, someday, when the laws are part of the language and not only documentation, we might be able to drop the superclass field of the dictionary by using the laws to recover the superclass in an instance-agnostic manner, e.g. with a non-overloaded function with type:

DictEq1 f -> DictEq a -> DictEq (f a)

But I don't wish to get into optomizations now, just demonstrate the close relationship between the law and the superclass.

RyanGlScott commented 2 years ago

I'm leery of making a breaking change to the definition of FromTextShow1 when a non-breaking change will do. I'll put up a proof-of-concept MR soon, based the instance context idea proposed in https://github.com/haskell/core-libraries-committee/issues/10#issuecomment-1166584371. (My apologies for pushing back a bit when you clearly put a lot of work into RyanGlScott/text-show#55, but I do think this can be made quite a bit simpler.)

Ericson2314 commented 2 years ago

@RyanGlScott Yeah sure that is fine, happy to hand it off. It is possible my PR is still an easier starting point to do that too but make the PR whoever you think is best.

Bodigrim commented 2 years ago

Dear CLC members, let's vote on https://gitlab.haskell.org/ghc/ghc/-/merge_requests/4727. The proposal fixes an issue with instances for Sum, Product and Compose being too rigid, and establishes a relation between Eq and Eq1 constraints and similar.

This is a breaking change, but the impact assessment (based on Stackage snapshot nightly-2022-06-17) shows only several packages affected, and we have PRs in place for all of them:

Breakage typically stems from defining instance Eq1 f without instance Eq a => Eq (f a). This can be fixed uniformly, by defining instance Eq a => Eq (f a) where (==) = liftEq (==).

@tomjaguarpaw @chessai @cgibbard @emilypi @mixphix


+1 from me, primarily for the reasons described in https://github.com/haskell/core-libraries-committee/issues/10#issuecomment-1166518746

mixphix commented 2 years ago

+1

Ericson2314 commented 2 years ago

Note I am updating the MR with the thing that @phadej mentioned in the GHC MR thread. Amended the description of this issue accordingly.

Ericson2314 commented 2 years ago

OK the PR is now up to date. The new revised *2 constraints I think should be uncontroversial. The default methods might be controversial and if so I am happy to remove them.

Bodigrim commented 2 years ago

@Ericson2314 The proposal was stable for half a year, I've spent the weekend on impact assessment, @RyanGlScott already patched several packages. Then we started a vote - and at this very moment you decided to pile up more breaking changes?.. This is not how it's supposed to work.

Please either revert your latest changes (and open a new proposal for them, if you wish), so that we can continue with a vote, or redo impact assessment afresh yourself.

tomjaguarpaw commented 2 years ago

The MR text is a bit odd. It starts off talking about Eq, then switches to Show before mentioning Ord. Was that intentional, for example to "mention the full range of changes"? I find it quite hard to read.

Ericson2314 commented 2 years ago

Sorry, I didn't mean to derail the process.

The change made dates back a year to the conversation between @phadej and I in https://gitlab.haskell.org/ghc/ghc/-/merge_requests/4727#note_357040 and is something that I had meant to add earlier but forgot about. I believe that change is very much in the spirit of the original (merely making the relationship between *2 and *1 match that between *1 and *) and so it felt more like a small correction to fix an oversight and complete what the proposal started, rather than dragging the MR in a new direction.

I looked over the packages that needed to be changed so far (in hopes that it would be an interesting subset) and I believe that all would continue to work with the existing (pre this last change) fixes. Indeed https://github.com/ChristopherDavenport/nonemptymap/pull/7/files already does the *1 classes in terms of the *2 classes.

If you confirm you still want me to revert it I will, but I would propose the reverted part as a follow-up change right after. And if we do want to do both, I would suggest getting them both done in the same release to "get the breakage over with".

Ericson2314 commented 2 years ago

OK while the the new super-classes I think are just better, I have no problem with holding off on the default methods since they are easy to add later but hard to remove. Keeping the latest constraints on the *2 classes but reverting the default methodsis a fine option too.

Bodigrim commented 2 years ago

@Ericson2314 could you please clarify the MR description with respect to issues mentioned in https://github.com/haskell/core-libraries-committee/issues/10#issuecomment-1167839334 ? Once ready, please sign off that you are happy with the final version of the proposal to be put forward.

Bodigrim commented 2 years ago

@Ericson2314 could we please make some progress here?

Ericson2314 commented 2 years ago

I am sorry for being slow/absent.

I have:

  1. Fixed the commit message as requested.
  2. Deleted the MR description (so there is one less thing to keep in sync, new description says look at commit message.) (Keep in mind that since GHC commits are rebased onto master, only the commit messages not MR description will live in version control.)
  3. Updated this issue's description to match the MR.

I think that is all that is asked of me, but if there is anything more do let me know. I will try to be properly on top of this.

Bodigrim commented 2 years ago

@tomjaguarpaw are you satisfied with the updates?

tomjaguarpaw commented 2 years ago

+1


Yes, all good by me, thanks.

Bodigrim commented 2 years ago

Dear CLC members, let's resume the vote, started in https://github.com/haskell/core-libraries-committee/issues/10#issuecomment-1166669613. CC @chessai @cgibbard @emilypi

@mixphix could you please confirm that your vote https://github.com/haskell/core-libraries-committee/issues/10#issuecomment-1166676009 is still valid?

mixphix commented 2 years ago

Yes, I'm still in favour. Thanks @Ericson2314 for the clarifications!

cgibbard commented 2 years ago

I'm still in favour as well. +1

emilypi commented 2 years ago

+1

Bodigrim commented 2 years ago

This gives us at least 5 votes in favor. Thanks all, approved.

Bodigrim commented 2 years ago

@Ericson2314 could you please prepare a migration guide for this change similar to https://github.com/haskell/core-libraries-committee/tree/main/guides ?

Ericson2314 commented 2 years ago

Opened https://github.com/haskell/core-libraries-committee/pull/84 with the migration guide.

mpickering commented 1 year ago

It appears there are some packages on stackage which need changes due to this proposal but weren't flagged in the impact assessment. Do you know why they were missed?

For example:

dual:

Control/Category/Dual.hs:23:10: error: [GHC-39999]
    • Could not deduce ‘Eq1 (Dual k a)’
        arising from the head of a quantified constraint
        arising from the superclasses of an instance declaration
      from the context: Eq2 k
        bound by the instance declaration
        at Control/Category/Dual.hs:23:10-30
      or from: Eq a
        bound by a quantified context at Control/Category/Dual.hs:23:10-30
    • In the instance declaration for ‘Eq2 (Dual k)’
   |
23 | instance Eq2 k => Eq2 (Dual k) where liftEq2 f g (Dual x) (Dual y) = liftEq2 g f x y

selective:

src/Control/Selective/Trans/Except.hs:51:7: error: [GHC-39999]
    • Could not deduce ‘Selective m’
        arising from the head of a quantified constraint
        arising from the 'deriving' clause of a data type declaration
      from the context: Monad m
        bound by a quantified context
        at src/Control/Selective/Trans/Except.hs:51:7-16
      Possible fix:
        add (Selective m) to the context of a quantified context
    • When deriving the instance for (MonadTrans (ExceptT e))
   |
51 |     , MonadTrans, MonadFix, MonadFail, MonadZip, MonadIO, MonadPlus, Eq1, Ord1
   | 

bencoding

src/Data/BEncode.hs:671:35: error: [GHC-39999]
    • No instance for ‘MonadPlus (Either String)’
        arising from the 'deriving' clause of a data type declaration
      Possible fix:
        use a standalone 'deriving instance' declaration,
          so you can specify the instance context yourself
    • When deriving the instance for (Alternative Get)
    |
671 |   deriving (Functor, Applicative, Alternative)
    |    

either-both:

Data/Either/Both.hs:17:10: error: [GHC-39999]
    • No instance for ‘Functor (Either' a)’
        arising from the head of a quantified constraint
        arising from the superclasses of an instance declaration
    • In the instance declaration for ‘Bifunctor Either'’
   |
17 | instance Bifunctor Either' where
   |          ^^^^^^^^^^^^^^^^^

quickcheck-state-machine:

[ 5 of 21] Compiling Test.StateMachine.Types.References ( src/Test/StateMachine/Types/References.hs, dist/
build/Test/StateMachine/Types/References.o, dist/build/Test/StateMachine/Types/References.dyn_o )

src/Test/StateMachine/Types/References.hs:94:10: error: [GHC-39999]
    • Could not deduce ‘Eq (Concrete a)’
        arising from the head of a quantified constraint
        arising from the superclasses of an instance declaration
      from the context: Eq a
        bound by a quantified context
        at src/Test/StateMachine/Types/References.hs:94:10-21
    • In the instance declaration for ‘Eq1 Concrete’
   |
94 | instance Eq1 Concrete where
   |   
phadej commented 1 year ago

Do you know why they were missed?

Because impact assessment is done in june of 2022? And probably against older Stackage LTS, which had different package set or/and older major versions.


In case of dual the fix is straight-forward, yet maybe not that satisfactory:

--- a/Control/Category/Dual.hs
+++ b/Control/Category/Dual.hs
@@ -1,7 +1,7 @@
 {-# LANGUAGE DerivingVia #-}
 module Control.Category.Dual where

-import Prelude (Eq, Ord, Read, Show, Bounded, ($))
+import Prelude (Eq ((==)), Ord (compare), Read, Show, Bounded, ($))

 import Control.Category
 import Data.Bifunctor
@@ -20,6 +20,9 @@ instance Category k => Category (Dual k) where
     id = Dual id
     Dual f . Dual g = Dual (g . f)

+instance (Eq2 k, Eq a) => Eq1 (Dual k a) where liftEq f (Dual x) (Dual y) = liftEq2 f (==) x y
+instance (Ord2 k, Ord a) => Ord1 (Dual k a) where liftCompare f (Dual x) (Dual y) = liftCompare2 f compare x y
+
 instance Eq2 k => Eq2 (Dual k) where liftEq2 f g (Dual x) (Dual y) = liftEq2 g f x y
 instance Ord2 k => Ord2 (Dual k) where liftCompare2 f g (Dual x) (Dual y) = liftCompare2 g f x y

@@ -31,6 +34,9 @@ instance Show2 k => Show2 (Dual k) where
     liftShowsPrec2 asp asl bsp bsl n =
         showsUnaryWith (liftShowsPrec2 bsp bsl asp asl) "Dual" n . dual

+instance Bifunctor k => Functor (Dual k a) where
+    fmap f = Dual . bimap f id . dual
+
 instance Bifunctor k => Bifunctor (Dual k) where
     bimap f g = Dual . bimap g f . dual

The problem is that there is no classes like

 class FunctorOn2 p where
    anotherFirst :: (a -> b) -> p a x -> p b x

so constraints for missing superclasses (Eq1, ..., Functor) will have overly restricted constraints. But at least we can write them, so it's not a blocker. (And because Functor (Dual k a) instance is "ugly" is probably a reason why it was omitted by the author).

For the reference Bifunctor superclass change is proposal #91 change


For quickchekc-state-machine the fix is

diff --git a/src/Test/StateMachine/Types/References.hs b/src/Test/StateMachine/Types/References.hs
index 9e4200d..89b59da 100644
--- a/src/Test/StateMachine/Types/References.hs
+++ b/src/Test/StateMachine/Types/References.hs
@@ -81,6 +81,8 @@ instance Ord1 Symbolic where
 data Concrete a where
   Concrete :: Typeable a => a -> Concrete a

+deriving stock instance Eq a => Eq (Concrete a)
+deriving stock instance Ord a => Ord (Concrete a)
 deriving stock instance Show a => Show (Concrete a)

 instance Show1 Concrete where

Especially the latter case is a problem of rolling stone uphill: without enforcement to have Eq a => Foo (Eq a) when you write Eq1 Foo instances, they will be omitted (cause humans makes mistakes). No different than Generically1 case https://github.com/haskell/core-libraries-committee/issues/10#issuecomment-955640705, these just happen until the change is released.

Bodigrim commented 1 year ago
chshersh commented 1 year ago

I'm trying to summarise the state of this proposal as part of my volunteering effort to track the progress of all approved CLC proposals.

Field Value
Author @Ericson2314
Status merged
base version 4.18.0.0
Merge Request (MR) https://gitlab.haskell.org/ghc/ghc/-/merge_requests/4727
Blocked by nothing
CHANGELOG entry present
Migration guide https://github.com/haskell/core-libraries-committee/blob/main/guides/functor-combinator-instances-and-class1s.md

Please, let me know if you find any mistakes 🙂