Opened 3 years ago
Last modified 12 months ago
#13153 new bug
Several Traversable instances have an extra fmap
Reported by: | dfeuer | Owned by: | dfeuer |
---|---|---|---|
Priority: | normal | Milestone: | 8.10.1 |
Component: | Core Libraries | Version: | 8.1 |
Keywords: | QuantifiedConstraints | Cc: | ekmett, goldfire |
Operating System: | Unknown/Multiple | Architecture: | Unknown/Multiple |
Type of failure: | Runtime performance bug | Test Case: | |
Blocked By: | Blocking: | ||
Related Tickets: | Differential Rev(s): | ||
Wiki Page: |
Description
For example, we define
instance Traversable ZipList where traverse f (ZipList xs) = ZipList <$> traverse f xs
If the list is very short, the extra fmap
could be bad. We can fix this by inlining the inner traverse
. However, I suspect a better approach would be to add a method to Traversable
:
mapTraverse :: Applicative f => (t b -> r) -> (a -> f b) -> t a -> f r mapTraverse p f xs = p <$> traverse f xs
but I need to work through whether this is enough power to solve enough problems.
Change History (17)
comment:1 follow-up: 2 Changed 3 years ago by
comment:2 Changed 3 years ago by
Replying to RyanGlScott:
Forgive my ignorance here, but how are you proposing to inline the inner
traverse
?In my mind, the only way I can see how you'd remove the
(<$>)
is if you had a special case forZipList []
.
You're confused about the definition.
newtype ZipList a = ZipList [a]
comment:3 Changed 3 years ago by
But that's exactly the definition I had in mind. What I was alluding to is that you could remove the (<$>)
is the case where the wrapped list is empty:
instance Traversable ZipList where traverse (ZipList []) = pure (ZipList [])
But what about this case?
traverse (ZipList (x:xs)) = ???
I'm not seeing how you can fill in this case without needing to appeal to fmap
or (<*>)
at some point.
comment:4 Changed 3 years ago by
We have (essentially)
instance Traversable [] where traverse f = foldr cons_f (pure []) where cons_f x = liftA2 (:) (f x)
Manually copying this idea into the ZipList
instance (I guess it's more than inlining) gives
instance Traversable ZipList where traverse f = foldr cons_f (pure (ZipList [])) . getZipList where cons_f x = liftA2 (\x' ys' -> ZipList (x' : getZipList ys')) (f x)
The point is to fuse the final ZipList <$>
into an operation that needs to happen anyway. ZipList
is actually a terrible choice of example, because lists usually aren't short enough for this to matter much. But if you look at something like First
or Sum
it's more obviously silly.
comment:5 follow-up: 8 Changed 3 years ago by
Ah, I see what you're getting at now.
It's quite unfortunate that we have to go through such contortions to make applying the newtype constructor zero-cost. We certainly could change the Traversable ZipList
implementation to what you suggest to avoid this quandary, but there's no getting around the fact that it's a hack.
One thing I've contemplated for a while is adding an unsafenewtype
deriving strategy that implements what Richard suggests in https://ghc.haskell.org/trac/ghc/ticket/9123#comment:27. That is, if you wrote:
{-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} newtype ZipList a = ZipList [a] deriving newtype (Functor, Foldable) deriving unsafenewtype (Traversable)
Then the derived Traversable ZipList
instance would be:
instance Traversable ZipList where traverse :: forall f a b. Applicative f => (a -> f b) -> ZipList a -> f (ZipList b) traverse = unsafeCoerce (traverse :: (a -> f b) -> [a] -> f [b])
Granted, this is a separate hack to get around the fact that we don't have higher-kinded roles yet, but it's (IMO) much nicer to use than having to manually inline the definition of traverse
like you demonstrated above.
comment:6 Changed 3 years ago by
--deleted--
(I thought for a moment the problematic <$>
was []
’s, where rule should optimize this away, but that is not the case.)
comment:7 Changed 3 years ago by
I am very skeptical of adding all these special functions to type classes. Should we not improve the optimiser so that users can write normal idiomatic definitions without having to understand these intricacies?
comment:8 Changed 3 years ago by
Replying to RyanGlScott:
newtype ZipList a = ZipList [a] deriving newtype (Functor, Foldable) deriving unsafenewtype (Traversable)
Interesting. I believe this is probably safe even if the underlying Applicative
and Traversable
are bogus, thanks to polymorphism. We are coercing f (t b)
to f (u b)
. The usual concern with such a coercion is that f
could have an index rather than a parameter, so matching on the result of the coercion could falsely reveal that t ~ u
. But traverse
can only construct f
values using pure
, <*>
, and the given function. Of those, only the given function could produce values carrying evidence. But they can carry evidence only about b
, not about t
. So it looks like coercing the result of traverse
to a representationally identical container with the same element type is probably okay.
Granted, this is a separate hack to get around the fact that we don't have higher-kinded roles yet, but it's (IMO) much nicer to use than having to manually inline the definition of
traverse
like you demonstrated above.
Can you explain how higher-kinded roles would help?
comment:9 Changed 3 years ago by
Cc: | goldfire added |
---|
Can you explain how higher-kinded roles would help?
Hm, I thought I meant higher-kinded roles, but now I recall Richard telling me that he thought those were inferior to normal roles + implication constraints (I've cc'd him in case I totally butcher this). So let me instead explain how those would help :)
The current issue that prevents you from writing this:
newtype Wrapped inner a = Wrap { unwrap :: inner a } deriving (Functor, Foldable) instance Traversable inner => Traversable (Wrapped inner) where traverse = coerce traverse
is that we need to coerce from (a -> f b) -> inner a -> f (inner b)
to (a -> f b) -> Wrapped a -> f (Wrapped b)
for some f
. That is, we need to prove Coercible (f (inner b)) (f (Wrapped b))
. But we don't know this a priori. f
is some arbitrary type variable, so we have to be conservative and assume its role is nominal. That prevents us from coercing underneath f
, so we can't conclude Coercible (f (inner b)) (f (Wrapped b))
.
But what if we could modify the Traversable
instance to require this coercibility property as part of the instance context? It sure would be great if we could just write this:
instance (Coercible (f (inner b)) (f (Wrapped inner b)), Traversable inner) => Traversable (Wrapped inner) where traverse :: forall f a b. Applicative f => (a -> f b) -> Wrapped inner a -> f (Wrapped inner b) traverse = coerce (traverse :: (a -> f b) -> Wrapped inner a -> f (Wrapped inner b))
But sadly, this won't work, since the b
and the f
in in the instance context can't scope over the class methods.
What implication constraints would let you do here is write this:
instance (forall f b. Applicative f => Coercible (f (inner b)) (f (Wrapped inner b)), Traversable inner) => Traversable (Wrapped inner) where traverse :: forall f a b. Applicative f => (a -> f b) -> Wrapped inner a -> f (Wrapped inner b) traverse = coerce (traverse :: (a -> f b) -> Wrapped inner a -> f (Wrapped inner b))
Notice that we're now able to stick a forall
inside of an instance context, something which GHC currently forbids! The idea here being that this forall f a b. Applicative f => Coercible (f (inner b)) (f (Wrapped inner b))
would get fed into the constraint solver and could be used to conclude that Coercible (f (inner b)) (f (Wrapped b))
works for any f
and b
(where f
is Applicative
).
But do keep in mind that user-visible implication constraints are nothing but a feature request at the moment, so all the above is hypothetical. Until some wonderful day in the future when we have this, the escape hatch is unsafeCoerce
.
comment:10 Changed 2 years ago by
Keywords: | QuantifiedContexts added |
---|
I'm adding the QuantifiedContexts
keyword only because implementing that feature (in the context of GeneralizedNewtypeDeriving
) would make this feature request obsolete.
comment:11 Changed 2 years ago by
Milestone: | 8.4.1 → 8.6.1 |
---|
This ticket won't be resolved in 8.4; remilestoning for 8.6. Do holler if you are affected by this or would otherwise like to work on it.
comment:12 Changed 23 months ago by
Keywords: | QuantifiedConstraints added; QuantifiedContexts removed |
---|
comment:13 Changed 22 months ago by
Oh dear. I now realize that my heart was in the right place when I wrote comment:9, but I goofed up several key details. I had written this instance:
instance (forall f b. Applicative f => Coercible (f (inner b)) (f (Wrapped inner b)), Traversable inner) => Traversable (Wrapped inner) where traverse :: forall f a b. Applicative f => (a -> f b) -> Wrapped inner a -> f (Wrapped inner b) traverse = coerce (traverse :: (a -> f b) -> Wrapped inner a -> f (Wrapped inner b))
But this is not quite what I wanted. The f
in the instance context is not the same f
as the f
in the type signature as traverse
, which is crucial. Indeed, the quantified constraint shouldn't go in the instance context at all, but rather in the method type signature itself:
instance Traversable inner => Traversable (Wrapped inner) where traverse :: forall f a b. (Applicative f, forall p q. Coercible p q => Coercible (f p) (f q)) => (a -> f b) -> Wrapped inner a -> f (Wrapped inner b) traverse = coerce (traverse :: (a -> f b) -> Wrapped inner a -> f (Wrapped inner b))
Of course, this isn't going to work either, because that's not actually the type signature for traverse
. If only that were the case!
But wait, there's something interesting going on here. f
is an instance of Applicative
and in turn an instance of Functor
. What exactly is Functor
, anyway? Here's the definition we all know and love:
class Functor f where fmap :: (a -> b) -> f a -> f b
If you squint really hard and look at the type signature for fmap
, it says "if you give me a coercion from a
to b
, then I can produce a coercion from f a
to f b
. That's awfully close to forall a b. Coercible a b => Coercible (f a) (f b)
! I'm going to be bold add suggest adding just that as a superclass of Functor
:
class (forall a b. Coercible a b => Coercible (f a) (f b)) => Functor f
(This is adapted from a similar suggestion here, which predates QuantifiedConstraints
.)
If we did this, we'd be able to newtype-derive Traversable
instances with no further changes, which is awesome! The downside, of course, is that we'd have to add a quantified constraint as a superclass of a Haskell Report class, at which many people would (understandably) turn up their noses.
If that option is too unpalatable, an alternative would be to add an additional class method to Traversable
with the right context:
class (Functor t, Foldable t) => Traversable t where traverse :: Applicative f => (a -> f b) -> t a -> f (t b) traverse' :: (Applicative f, forall p q. Coercible p q => Coercible (f p) (f q)) => (a -> f b) -> t a -> f (t b) traverse' = traverse
Then, folks who really care about performance could implement traverse' = coerce (traverse' :: ...)
themselves and use that. However, you still wouldn't be able to newtype-derive Traversable
with this approach, and it's rather unsatisfying in that performance-minded programmers would have to switch over all of their traverse
s to traverse'
s. (And arguably, every programmer should be performance-minded anyway!)
In any case, this situation is clearly more complicated than I originally imagined, and I imagine that any solution we could pick will have its share of drawbacks.
comment:14 Changed 22 months ago by
If only we had mapTraverse
instead of traverse
as the class method, none of this mess would be necessary. That would obviously be a hard sell for backwards compatibility.
comment:16 Changed 18 months ago by
Milestone: | 8.6.1 → 8.8.1 |
---|
These will not be addressed in GHC 8.6.
comment:17 Changed 12 months ago by
Milestone: | 8.8.1 → 8.10.1 |
---|
Bumping milestones of low-priority tickets.
Forgive my ignorance here, but how are you proposing to inline the inner
traverse
?In my mind, the only way I can see how you'd remove the
(<$>)
is if you had a special case forZipList []
.