Closed Ericson2314 closed 2 years ago
When I rebased this, I found that Generically1
was missing Eq
, Ord
, Show
, and Read
instances, even though it had the *1
versions. Classic!
https://github.com/haskellari/some/pull/21 This is an example of an downstream library improvement that is blocked on this change.
GShow f = forall a. Show (f a)
for all intents and purposes, but we cannot make a superclass to indicate (half of) that because the GShow
instances for Sum
and Product
conflict with the overly-conservative Show1
-based instances we have today, instead of the strictly more general instances proposed here.
The canonicity law looks good to me -- I'm actually surprised that Eq1
and co didn't already have something like this. The quantified constraint superclass also looks fine and sensible to me.
If we're going to use FlexibleContexts
-style Eq (f a)
constraints around the place after this change, what reason do Eq1
and co still have for existing? I thought their main purpose was to avoid such FlexibleContexts
-style code.
Do we know how much of hackage this breaks? It looks like there was some effort to run this against head.hackage
but nobody understood the outcome?
If we're going to use
FlexibleContexts
-styleEq (f a)
constraints around the place after this change, what reason doEq1
and co still have for existing? I thought their main purpose was to avoid suchFlexibleContexts
-style code.
Besides back-compat (just getting rid of the classes altogether would be far more breaking), the classes are still meaningful if one wants to lift a non-canonical function on the inside. I am not sure how often that is done, but it's theoretically useful enough that I don't feel inspired to rid of this.
Do we know how much of hackage this breaks? It looks like there was some effort to run this against
head.hackage
but nobody understood the outcome?
I will try running it again. I think it was just broken then, but might work now.
Eq1
class is still meaningful, because it allows to check heterogeneous equality like "does f a
matches f b
?".
Thanks, I now agree that Eq1
and friends still have reason to exist.
@Ericson2314 did the GHC CI help you with an impact analysis?
along with some laws that canonicity is preserved
Are these laws unconditional or are they expecting that an underlying (==)
is lawful? (I'm thinking about instance Ord1 Down
issues)
This is something I'd also love to see some impact analysis on, but I can imagine most users of the *1 classes being happy about the improvement, even if it might involve knocking out some forgotten instances. I'd also personally be happy about the fixes for Compose
. So this is a tentative +1 from me, unless we somehow see that the world would be covered in tiny fires.
I'm tentatively in favor of this proposal, it reflects my experience with *1
classes and QuantifiedContraints
. But we really need an impact assessment to understand what we are voting for.
@phadej could you possible please share instructions how to test changes to base
against Stackage, as you did in https://github.com/haskell/core-libraries-committee/issues/3#issuecomment-953389734 ?
The canonicity law looks good to me -- I'm actually surprised that Eq1 and co didn't already have something like this. The quantified constraint superclass also looks fine and sensible to me.
The Eq1
class today doesn't have any relationship with Eq
, thus stating the liftEq (==) = (==)
law is awkward. Quantified super constraint adds necessary bits so the law always type-checks.
the classes are still meaningful if one wants to lift a non-canonical function on the inside. I am not sure how often that is done, but it's theoretically useful enough that I don't feel inspired to rid of this.
E.g. QuickCheck
listOf
combinator is very much used, it's a special case of liftArbitrary
. i also use liftShowsPrec
quite a lot to show lists of things which don't (or cannot) have good Show
instance (or have bad one).
Are these laws unconditional or are they expecting that an underlying (==) is lawful? (I'm thinking about instance Ord1 Down issues)
I'd say it's fair to assume that (==) :: a -> a -> Bool
is lawful. We can say that for every reflexive, transitive f
, liftEq f
is also reflexive and transitive: That is relaxed version as liftEq f _ _ = True
is trivially reflexive and transitive for any f
, but otoh it's stricter as liftEq
implementation may assume that f
is reflexive and transitive.
could you possible please share instructions how to test changes to base against Stackage
I'll try to do that asap. (They aren't complicated, but not entirely trivial). A good starting point is to have a patch applied to a version of GHC and base which has stackage snapshot (e.g. 9.0.1 or 8.10.x). Migrating stackage to ghc-head is too much work.
Thanks for mentioning @phadej that the laws are awkward to have without the superclass. That is an added benefit I forgot.
The MR had a error I think I just figured out --- a test needed to be updated, but it was in the haddock submodule so my git diff
missed it. When it rebuilds I think there is a button I can hit to make it do a head.hackage run.
Are these laws unconditional or are they expecting that an underlying (==) is lawful?
I think they need not relay on a sane underlying (==)
. e.g. [NaN, Nan] :: [Double]
should not be equal to itself, right?
In fact,
liftEq f = and . liftA2 f
liftCompare f = foldr thenCmp EQ . liftA2 f
might be valid laws too. But I don't know what the cost of those super-classes would be, and especially thenCmp
not being associative, so I rather punt on that until later :).
There are also wrappers in other core-ish libraries, e.g. Reverse
and Backwards
:
Would be nice if instances were uniform for these.
Does this proposal break or not code like:
class Eq1 t => Hashable1 t where ...
instance (Hashable1 f, Hashable1 g) => Hashable1 (Compose f g) where ...
I have to think about this, so probably a good idea to explicitly write the answer down in the proposal.
I'm also tentatively +1
@phadej just a gentle reminder about https://github.com/haskell/core-libraries-committee/issues/10#issuecomment-968068641
@Ericson2314 any chance to test against head.hackage?
@Bodigrim as I said, the first step is to have a patch against a GHC version which has a stackage snapshot. GHC master
and having to use head.hackage
just adds to much variables, that it's not feasible IMO.
Then the simple approach is to create a cabal package with
cabal.config
(add it to a url of a snapshot e.g. https://www.stackage.org/nightly-2021-12-17/cabal.config) changing
constraints
to build-depends
installed
packagescabal build
executable
only. You may remove them or move to build-tool-depends
(but then you need to figure out the executable names, which usually are the same as package ...)This approach also ignores flags as cabal.config
doesn't have them. (It could add constraints: foo +flag
, but it doesn't, those can be added to cabal.project
then).
This all can be automated, by
cabal-install-parsers
to read the index (to figure out which packages are executables, diagnostics mentioned above)And one general tip is to do 100 packages at the time, by first doing cabal build --dry
: Solver in all cabal installs is slow when there are many direct
dependencies (i think it's improved in master
), as build plans will fail and
you'll need to figure out missing native dependencies or just disable these
packages. Such metadata would be great to have up front, and the tool would
figure that out directly as here we are not really solving anything.
It might be it's slow because I didn't constraint flags,
so solver tries to flip them.
The Hashable instance is fine. See how the Eq1 instance for Compose is unaffected on the patch. I would recommend those packages adjust the definition of Hashable itself analogously, but it's not mandatory.
Hmm I thought this testing stuff was already automated, but I guess not.
@Ericson2314 any chance for impact assessment please? I'd like to resolve this one way or another.
Sorry, I have not blocked out the chunk of time needed to get through that fairly manual process yet. I will try to bump this forward in my queue of things to do.
@Ericson2314 I've created https://github.com/Bodigrim/clc-stackage, which is a meta-package for the majority of libraries in Stackage Nightly. Essentially all you need to do is to backport your changes to base-4.15, compile GHC from 9.0 branch and run cabal build -w ghc-9.0.your_patch
. You can further provide fixes for affected packages via local copies, referenced from cabal.project
. This should give a rough idea how much is broken.
Thanks @Bodigrim. I am hoping after https://github.com/haskellfoundation/tech-proposals/pull/27 goes though this process will be quite polished, and then I will give this a shot.
Separately, doing
git log libraries/base/Data/Functor/Classes.hs
turned up https://github.com/ghc/ghc/commit/e0e03d5b9d5cd678f6402534451964d491f16540 which linked https://mail.haskell.org/pipermail/libraries/2015-July/026014.html
It looks like these *1
classes were only added to base based of the data types that use that had these instances. With this (or #35), those data types no longer need those *1
classes to implement the more basic ones. What that means is that we can invert the dependency and make the modules with *1
classes depend on those data types instead.
This makes me also want to just remove the Ord1
classes from base
entirely! So
functor-classes
packageThe question remains, should this be done right away, or as a successive step in a longer deprecation cycle?
I propose that https://gitlab.haskell.org/ghc/ghc/-/issues/20647 / https://discourse.haskell.org/t/re-pre-pre-hftp-decoupling-base-and-ghc/4269/3 gives us an alternative.
base
to ghc-base
in the GHC repo, with base
a trivial package (in another repo) that reexports ghc-base
.Fork out functor-classes
, making it depend on ghc-base
, and make base
reexport functor-classes
too.
After a deprecation cycle, get rid of the functor-classes
re-export.
This means we still get a smooth migration, but the benefit of making obscure stuff out of tree immediately. This woks best if https://gitlab.haskell.org/ghc/ghc/-/issues/4879 / https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0134-deprecating-exports-proposal.rst is finally implemented, so those reexports can be deprecated immediately.
edit actually https://github.com/ghc-proposals/ghc-proposals/discussions/489 is what is needed since these are module not definition reexports, and we want base
and functor-classes
to not export technically different modules with overlapping names,
Several instances were omitted from Generically1
, both to simplify its inclusion and in an effort to make deriving X via Generically(1) D
match deriving stock X
as closely as possible. The Read(1)
and Show(1)
instances were not part of that selected instances. I will make an issue proposing the addition to Eq
and Ord
but they are subtly different. With data D = D deriving stock Eq
we get undefined == D
= undefined
. However deriving via Generically1 D
gives undefined == D
= True
.
I tried to run a quick-and-dirty impact assessment. Most of the packages are fine (indeed, it is rare to define instance Eq1 f
without defining instance Eq (f a)
nearby), but transformers-compat
is seriously affected, because it contains a Generic mechanism to derive Eq1
and friends:
Building library for transformers-compat-0.7.1..
[1 of 4] Compiling Control.Monad.Trans.Instances
[2 of 4] Compiling Data.Functor.Classes.Generic.Internal
generics/Data/Functor/Classes/Generic/Internal.hs:819:10: error:
• Could not deduce (Eq (FunctorClassesDefault f a))
arising from the superclasses of an instance declaration
from the context: (GEq1 NonV4 (Rep1 f), Generic1 f)
bound by the instance declaration
at generics/Data/Functor/Classes/Generic/Internal.hs:819:10-75
or from: Eq a
bound by a quantified context
at generics/Data/Functor/Classes/Generic/Internal.hs:1:1
• In the instance declaration for ‘Eq1 (FunctorClassesDefault f)’
|
819 | instance (GEq1 NonV4 (Rep1 f), Generic1 f) => Eq1 (FunctorClassesDefault f) where
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
@RyanGlScott what do you think?
Hm. FunctorClassesDefault
is basically Generically1
, although it provides more instances than Generically1
does (Read1
and Show1
). I tried to see how Generically1
's Eq1
instance works, and it's simpler than expected:
instance (Generic1 f, Eq (Rep1 f a)) => Eq (Generically1 f a)
I say "simpler than expected" because I think you would achieve pretty counterintuitive results if you tried to actually derive an Eq
instance via Generically1
. Here is an example which illustrates this:
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE StandaloneKindSignatures #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE UndecidableInstances #-}
module Foo where
import Data.Functor.Classes
import Data.Kind
import GHC.Generics
type Generically1 :: forall k. (k -> Type) -> (k -> Type)
newtype Generically1 f a where
Generically1 :: forall {k} f a. f a -> Generically1 @k f a
instance (Generic1 f, Eq (Rep1 f a)) => Eq (Generically1 f a) where
Generically1 x == Generically1 y = from1 x == from1 y
Generically1 x /= Generically1 y = from1 x /= from1 y
instance (Generic1 f, Eq1 (Rep1 f)) => Eq1 (Generically1 f) where
liftEq :: (a1 -> a2 -> Bool) -> (Generically1 f a1 -> Generically1 f a2 -> Bool)
liftEq (===) (Generically1 as1) (Generically1 as2) = liftEq (===) (from1 as1) (from1 as2)
type T :: (Type -> Type) -> (Type -> Type) -> Type -> Type
data T f g a = MkT (f (g a))
deriving stock Generic1
deriving Eq via Generically1 (T f g) a
Surprisingly, this doesn't work:
[1 of 1] Compiling Foo ( Foo.hs, interpreted )
Foo.hs:33:12: error:
• No instance for (Eq (f (Rec1 g a)))
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 (Eq (T f g a))
|
33 | deriving Eq via Generically1 (T f g) a
| ^^
In order to make this work, you have to carefully use StandaloneDeriving
to give it the right instance context:
deriving via Generically1 (T f g) a instance (Eq (f (Rec1 g a)), Functor f) => Eq (T f g a)
Note that the instance context mentions leaks the generic representation type Rec1
, which is usually considered a datatype-generic programming faux pas. The instance would probably work if you used it, but I could think of more straightforward ways to define this instance.
Returning back to the topic of FunctionClassesDefault
, I think it would suffice to give it an Eq
instance like this:
instance (GEq (Rep1 f a), Generic1 f) => Eq (FunctorClassesDefault f a) where
FunctorClassesDefault x == FunctorClassesDefault y = eqDefault x y
class GEq a where
geq :: a -> a -> Bool
-- Provide all of the usual instances for GEq
eqDefault :: (GEq (Rep1 f a), Generic1 f) => f a -> f a -> Bool
eqDefault m n = geq (from1 m) (from1 n)
And then give GEq1
a quantified superclass on sufficiently recent versions of GHC:
class (forall a. Eq a => GEq (t a)) => GEq1 v t where
-- ...
The trickiest part is coming up with the GEq
instance for (:.:)
. Here is the best thing I have come up with:
instance (Eq1 f, GEq (g p)) => GEq ((f :.: g) p) where
geq (Comp1 m) (Comp1 n) = liftEq geq m n
With this approach, if you were to derive an Eq
instance for T
via FunctorClassesDefault
, you'd end up with:
instance (Eq1 f, Eq1 g, Eq a, Functor f) => Eq (T f g a)
This seems pretty consistent with the behavior of the derived Eq1
instances, so I'd be happy with this. When I have some more time, I can port over all of transformers-compat
's generic machinery to use this approach. Luckily, it should be backwards-compatible to do so.
Thanks for investigation and analysis, @RyanGlScott.
@Ericson2314 the progress of the proposal mostly depends on updating transformers-compat
in a backwards-compatible way. Maybe you can help Ryan with it?..
Thank you both very much!!!! I'll happily help out @RyanGlScott with that.
@Ericson2314, I've opened ekmett/transformers-compat#54, which I believe should future-proof transformers-compat
against this change to the superclasses of Eq1
and friends. I don't have a local build of https://gitlab.haskell.org/ghc/ghc/-/merge_requests/4727 handy, so would you be willing to test that patch? cabal test transformers-compat-tests
should suffice.
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)
That would be a very welcome change, I think. The reason is that Compose f g a
is kind-polymorphic:
> import Data.Functor.Compose
> :k Compose
Compose :: (k -> *) -> (k1 -> k) -> k1 -> *
But you cannot have Eq1 g
for g :: k1 -> k
, because Eq1
demands g :: * -> *
:
> import Data.Functor.Classes
> :k Eq1
Eq1 :: (* -> *) -> Constraint
It gets especially embarassing when a
is a phantom type: it does not interact at all with Eq
instance, and still one cannot define Eq (Compose f g a)
.
After some thought, I've realized that the strange Eq (f (Rec1 g a))
constraint that arises when trying to derive an Eq
instance via Generically1
(as seen in https://github.com/haskell/core-libraries-committee/issues/10#issuecomment-1166302780) isn't really the fault of this proposal, but rather due to the unusual way that (:.:)
is used derived Generic1
instances. #75 is a proposal to change the conventions surrounding (:.:)
. If I were to derive an Eq
instance via Generically1
using the conventions suggested in that proposal:
Then the derived Eq
instance for T
becomes:
instance Eq (f (g a)) => Eq (T f g a)
Which is exactly what we want in this proposal. Therefore, I'm not too bothered by the strangeness observed in https://github.com/haskell/core-libraries-committee/issues/10#issuecomment-1166302780. That's due to a quirk in the way deriving Generic1
works, not this proposal.
Also, thank you to @Bodigrim for testing the patch in ekmett/transformers-compat#54. I've released transformers-compat-0.7.2
to Hackage with these changes.
Thanks for your work and quick response, @RyanGlScott, much appreciated.
I made some further progress with impact assessment. Several packages are easy to fix:
source-repository-package
type: git
location: https://github.com/Bodigrim/streaming.git
source-repository-package
type: git
location: https://github.com/Bodigrim/free.git
source-repository-package
type: git
location: https://github.com/Bodigrim/nonemptymap.git
The next stumbling block is text-show
. It introduces a hierarchy of TextShow
, TextShow1
and TextShow2
, which is now subtly broken. Not sure what's the best course of actions here.
src/TextShow/FromStringTextShow.hs:175:10: error:
• Could not deduce (TextShow a)
arising from the superclasses of an instance declaration
from the context: Show a
bound by a quantified context
at src/TextShow/FromStringTextShow.hs:1:1
Possible fix:
add (TextShow a) to the context of a quantified context
• In the instance declaration for ‘Show1 FromTextShow’
|
175 | instance Show1 FromTextShow where
| ^^^^^^^^^^^^^^^^^^
src/TextShow/FromStringTextShow.hs:328:10: error:
• Could not deduce (TextShow a)
arising from the superclasses of an instance declaration
from the context: TextShow1 f
bound by the instance declaration
at src/TextShow/FromStringTextShow.hs:328:10-47
or from: Show a
bound by a quantified context
at src/TextShow/FromStringTextShow.hs:1:1
Possible fix:
add (TextShow a) to the context of a quantified context
• In the instance declaration for ‘Show1 (FromTextShow1 f)’
|
328 | instance TextShow1 f => Show1 (FromTextShow1 f) where
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
src/TextShow/FromStringTextShow.hs:502:10: error:
• Could not deduce (TextShow a1)
arising from the superclasses of an instance declaration
from the context: (TextShow2 f, TextShow a)
bound by the instance declaration
at src/TextShow/FromStringTextShow.hs:502:10-63
or from: Show a1
bound by a quantified context
at src/TextShow/FromStringTextShow.hs:1:1
Possible fix:
add (TextShow a1) to the context of a quantified context
• In the instance declaration for ‘Show1 (FromTextShow2 f a)’
|
502 | instance (TextShow2 f, TextShow a) => Show1 (FromTextShow2 f a) where
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
src/TextShow/FromStringTextShow.hs:509:10: error:
• Could not deduce (TextShow a)
arising from the superclasses of an instance declaration
from the context: TextShow2 f
bound by the instance declaration
at src/TextShow/FromStringTextShow.hs:509:10-47
or from: (Show a, Show b)
bound by a quantified context
at src/TextShow/FromStringTextShow.hs:1:1
Possible fix:
add (TextShow a) to the context of a quantified context
• In the instance declaration for ‘Show2 (FromTextShow2 f)’
|
509 | instance TextShow2 f => Show2 (FromTextShow2 f) where
| ^^^^^^^^^^^^^^^^
The closest I can get is https://github.com/Bodigrim/text-show/commit/e4fc3c759a9e601063882c303c1bb6c2b4e9bd4c, but forall a. Show a => TextShow a
is a bit weird. @RyanGlScott, sorry to bother you, may I ask for your opinion on this please?
This is interesting. I think we have two options here
Delete Show1 FromTextShow
for being incorrect now, because having a Show a
is not sufficient to have a Show (FromTextShow a)
: one instead needs a TextShow a
and that is indeed the very point of this class.
Add a Show a
superclass to TextShow a
, requiring every TextShow
instance to have a matching Show
instance. That would work, but is against the sort of usage where one is trying to avoid Show
entirely.
instance (forall a. Show a => TextShow a) => Show1 FromTextShow
is tantamount to option 1, because that constraint will never be satisfied.
This is a tricky one, and I don't yet have a good idea of how to adapt this code.
FromTextShow
is a newtype used for deriving Show
instances via TextShow
. There is a similar relationship between FromTextShow1
/Show1
/TextShow1
and FromTextShow2
/Show2
/TextShow2
. I'll focus on FromTextShow1
's instances for now:
instance (TextShow1 f, TextShow a) => Show (FromTextShow1 f a)
instance TextShow1 f => Show1 (FromTextShow1 f)
When Show1
has a quantified superclass, GHC will reject the Show1
instance for FromTextShow1
:
src/TextShow/FromStringTextShow.hs:355:10: error:
• Could not deduce (TextShow a)
arising from the superclasses of an instance declaration
from the context: TextShow1 f
bound by the instance declaration
at src/TextShow/FromStringTextShow.hs:355:10-47
or from: Show a
bound by a quantified context
at src/TextShow/FromStringTextShow.hs:1:1
Possible fix:
add (TextShow a) to the context of a quantified context
• In the instance declaration for ‘Show1 (FromTextShow1 f)’
|
355 | instance TextShow1 f => Show1 (FromTextShow1 f) where
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
And indeed, the Show
instance has TextShow a
in its instance context, but the Show1
instance doesn't satisfy that constraint. My first inclination was to change the context in the Show
instance:
instance TextShow (f a) => Show (FromTextShow1 f a)
That changes the error message to:
src/TextShow/FromStringTextShow.hs:358:10: error:
• Could not deduce (TextShow (f a))
arising from the superclasses of an instance declaration
from the context: TextShow1 f
bound by the instance declaration
at src/TextShow/FromStringTextShow.hs:358:10-47
or from: Show a
bound by a quantified context
at src/TextShow/FromStringTextShow.hs:1:1
• In the instance declaration for ‘Show1 (FromTextShow1 f)’
|
358 | instance TextShow1 f => Show1 (FromTextShow1 f) where
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
OK, fair enough. Next, I gave TextShow1
a quantified superclass:
class (forall a. TextShow a => TextShow (f a)) => TextShow1 f where
-- ...
But that just changes the error message back to what it was originally!
src/TextShow/FromStringTextShow.hs:358:10: error:
• Could not deduce (TextShow a)
arising from the superclasses of an instance declaration
from the context: TextShow1 f
bound by the instance declaration
at src/TextShow/FromStringTextShow.hs:358:10-47
or from: Show a
bound by a quantified context
at src/TextShow/FromStringTextShow.hs:1:1
Possible fix:
add (TextShow a) to the context of a quantified context
• In the instance declaration for ‘Show1 (FromTextShow1 f)’
|
358 | instance TextShow1 f => Show1 (FromTextShow1 f) where
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
And as @Ericson2314 notes in https://github.com/haskell/core-libraries-committee/issues/10#issuecomment-1166567641, I wouldn't be happy with putting forall a. Show a => TextShow a
in the instance context, as that almost assuredly wouldn't work if you tried using it in practice.
In short, I'm stuck. Any ideas?
- Delete
Show1 FromTextShow
for being incorrect now, because having aShow a
is not sufficient to have aShow (FromTextShow a)
: one instead needs aTextShow a
and that is indeed the very point of this class.
We may well need to do this, but it's worth noting that this is a separate issue from the FromTextShow1
instance issue I describe above. I genuinely have no clue how to fix that one.
- Add a
Show a
superclass toTextShow a
, requiring everyTextShow
instance to have a matchingShow
instance. That would work, but is against the sort of usage where one is trying to avoidShow
entirely.
Yuck. I really hope it doesn't come to that.
@RyanGlScott FromTextShow1 f :.: FromStringShow
and FromStringShow1 f :.: FromTextShow
do morally have Show1
and TextShow1
instances.
I suggested we
*1
and *2
classes.FromTextShow
and FromShow
.FWIW, note that the new adapters vaguely resemble profunctors in that one is mapping the instance one way before, and then mapping it back after.
I'm afraid I don't quite understand the plan you're proposing. Can you describe your plan in more detail, particularly steps (2) and (3)?
For what it's worth, the only FromTextShow1
instance that I really care about is its Show1
instance—I'd really prefer not to change that if possible. Its Show
instance is mostly there for the sake of completeness, however, and I'm happy to rearrange it as needed to make things typecheck. Similarly for FromTextShow2
.
@RyanGlScott Ah sorry I was talking about the instances on the non-*1
newtypes.
I'll give the *1
newtypes some thought too, but also I think I better actually try out what ever sort of build you both are using so I can get some concrete errors.
In the mean time, @Ericson2314, could you please rebase https://gitlab.haskell.org/ghc/ghc/-/merge_requests/4727?
Sure!
Thanks, @Ericson2314. FWIW, I've been prototyping things by simply redefining Show1
and Show2
locally with the quantified superclasses, which is far easier than building all of GHC.
@RyanGlScott OK so I think we need
-instance (TextShow1 f, TextShow a) => Show (FromTextShow1 f a)
+instance (TextShow1 f, Show a) => Show (FromTextShow1 f a)
And then Show1 (FromTextShow1 f)
can be written again.
The new Show
instance would do (_ :: TextShowImpl -> ShowImpol) . TextShow1 f . (_ :: ShowImpl -> TextShowImpl)
if that makes any sense.
To accomplish that I think we can change the definition of FromTextShow1
to help (I'll write that next).
-newtype FromTextShow1 f a = FromTextShow1 { fromTextShow1 :: f a }
+newtype FromTextShow1 f a = FromTextShow1
+ { fromTextShow1 :: FromTextShow (f (FromStringShow a))
+ }
and likewise
-newtype FromStringShow1 f a = FromStringShow1 { fromStringShow1 :: f a }
+newtype FromStringShow1 f a = FromStringShow1
+ { fromStringShow1 :: FromStringShow (f (FromTextShow a))
+ }
I completed the impact assessment. The only Stackage packages which need patches are:
source-repository-package
type: git
location: https://github.com/Bodigrim/kan-extensions.git
source-repository-package
type: git
location: https://github.com/Bodigrim/text-show.git
source-repository-package
type: git
location: https://github.com/Bodigrim/streaming.git
source-repository-package
type: git
location: https://github.com/Bodigrim/nonemptymap.git
source-repository-package
type: git
location: https://github.com/Bodigrim/sexp-grammar.git
subdir: sexp-grammar
source-repository-package
type: git
location: https://github.com/Bodigrim/sandwich.git
subdir: sandwich
Of which everything except text-show
looks pretty straightforward. That said, the future progress on the proposal depends on sorting out a strategy for text-show
.
I am working on text-show
.
OK so I think we need
-instance (TextShow1 f, TextShow a) => Show (FromTextShow1 f a) +instance (TextShow1 f, Show a) => Show (FromTextShow1 f a)
And then
Show1 (FromTextShow1 f)
can be written again.
Sounds good to me. It's a bit of a shame that we have to do this solely for the sake of satisfying the superclass constraints, but at the same time, I don't have any better ideas.
The new
Show
instance would do(_ :: TextShowImpl -> ShowImpol) . TextShow1 f . (_ :: ShowImpl -> TextShowImpl)
if that makes any sense.To accomplish that I think we can change the definition of
FromTextShow1
to help (I'll write that next).
Er, why do we need to do this? Wouldn't it suffice to just implement the Show
instance as showsPrec = showsPrec1
?
See https://github.com/RyanGlScott/text-show/pull/55. Unfortunately I am scrambling to move so I don't think I will have time to work on it any more for the next few days, but it should hopefully make some sense in the interim?
To accomplish that I think e can change the definition of FromTextShow1 to help (I'll write that next).
Er, why do we need to do this?
I thought it would be nice to keep track in the types of all the instances that need converting, But I am not sure I did that well, and the fact that F
might not be representational is annoying.
On the other hand, it my allow avoiding the *1
/*2
classes by making the conversion canonical. That in the spirit of this issue, which has a goal of the quantified constraints to replacing those classes as much as possible.
Implementation https://gitlab.haskell.org/ghc/ghc/-/merge_requests/4727
The first change makes the
Eq
,Ord
,Show
, andRead
instances forSum
,Product
, andCompose
match those for:+:
,:*:
, and:.:
. These have the proper flexible contexts that are exactly what the instance needs:For example, instead of
we do
But, that change alone is rather breaking, because until now
Eq (f a)
andEq1 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:along with some laws that canonicity is preserved, like:
and likewise for
*2
classesalong with some laws that canonicity is preserved, like:
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
, andCompose
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 forTree
andOrd
, which I fixed in https://github.com/haskell/containers/pull/761, but fixing the issue by addingOrd1
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:
But I don't wish to get into optomizations now, just demonstrate the close relationship between the law and the superclass.