[GHC] #13328: Foldable, Functor, and Traversable deriving handle phantom types badly

#13328: Foldable, Functor, and Traversable deriving handle phantom types badly -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.1 Keywords: deriving-perf | Operating System: Unknown/Multiple Architecture: | Type of failure: Runtime Unknown/Multiple | performance bug Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Suppose we have {{{#!hs data Phantom a = Z | S (Phantom a) }}} We'd like to get something like {{{#!hs foldMap _ _ = mempty fmap = coerce traverse _ m = pure (coerce m) }}} But instead we actually pattern match all the way down! Basically, we want to treat "has a phantom role" and "does not occur" similarly. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13328 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13328: Foldable, Functor, and Traversable deriving handle phantom types badly -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: deriving-perf Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): That proposed `foldMap` implementation has different strictness properties than the current one that `deriving` Foldable uses. That is, this program: {{{#!hs {-# LANGUAGE DeriveFoldable #-} data Phantom a = Z | S (Phantom a) deriving Foldable main :: IO () main = print $ foldMap (const ()) (undefined :: Phantom Int) }}} will throw an exception, whereas this program: {{{#!hs data Phantom a = Z | S (Phantom a) instance Foldable Phantom where foldMap _ _ = mempty main :: IO () main = print $ foldMap (const ()) (undefined :: Phantom Int) }}} will output `()`. I like the intent of this proposal, however. Can the strictness problem be fixed by changing it to `foldMap _ !_ = mempty`/`foldr _ z !_ = z`? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13328#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13328: Foldable, Functor, and Traversable deriving handle phantom types badly -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: deriving-perf Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): No, you have to pick efficiency or strictness here. The bottom could show up anywhere down the line. I think derived instances should generally go for what someone's likely to write by hand, rather than trying to imitate the lousy results of the default. The default implementation of `null` will diverge on an infinite snoc-list, but that doesn't mean the derived implementation should. I think the same is true here. If the type is phantom, there's no possible reason to go there, so we shouldn't. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13328#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13328: Foldable, Functor, and Traversable deriving handle phantom types badly -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: deriving-perf Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I do agree that your proposed definition is probably the better one. I only ask that we point out this change in strictness in the users' guide (and probably the migration guide for whatever GHC release this makes it into) so that users aren't too surprised. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13328#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13328: Foldable, Functor, and Traversable deriving handle phantom types badly -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: deriving-perf Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Two more thoughts to consider. One: how should this interact with your feature request in #13117? That is, you had previously requested that if you wrote this: {{{#!hs data V a deriving Functor }}} then GHC should generate this: {{{#!hs instance Functor V where fmap _ x = case x of {} }}} But `V`'s type parameter is phantom here, so you could just as well implement it like this (as Eric Mertens originally pointed out in https://mail.haskell.org/pipermail/libraries/2017-January/027603.html): {{{#!hs instance Functor V where fmap _ = coerce }}} Which choice should we make here? Two (a follow-up question to comment:1, after reading Eric's comment about role annotations in https://mail.haskell.org/pipermail/libraries/2017-January/027603.html): consider this code: {{{#!hs data Foo a = Foo deriving instance Foldable Foo }}} In this scenario, the type parameter to `Foo` is phantom, so the generated `Foldable` instance is: {{{#!hs instance Foldable Foo where foldMap _ _ = mempty }}} Now what happens if you add a role annotation to `Foo`? {{{#!hs type role Foo nominal data Foo a = Foo deriving instance Foldable Foo }}} Now, since `Foo`'s type parameter is no longer phantom, the generated `Foldable` instance will be: {{{#!hs instance Foldable Foo where foldMap _ Foo = mempty }}} That is to say, the choice of role can affect what the strictness of `foldMap` will be. Is this desirable? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13328#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13328: Foldable, Functor, and Traversable deriving handle phantom types badly -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: deriving-perf Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): There's one more scenario that this proposed change would wreak havoc with. It's quite possible for users to define unlawful `Functor` instances and depend on them in other derived `Functor` instances: {{{#!hs newtype Unlawful a = Unlawful Int instance Functor Unlawful where fmap f (Unlawful i) = Unlawful (i + 1) newtype WrapUnlawful a = WrapUnlawful (Unlawful a) deriving Functor }}} But under this proposal, the generated `Functor` instance for `WrapUnlawful` would be: {{{#!hs instance Functor WrapUnlawful where fmap _ = coerce }}} This would be another departure in behavior, as now `fmap`ping over a `WrapUnlawful` wouldn't apply `(+1)` to the field of the `Unlawful` (icky as it may be). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13328#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13328: Foldable, Functor, and Traversable deriving handle phantom types badly -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: deriving-perf Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): The question about `fmap` strictness looks like a red herring to me. There's no real difference between the empty case definition and the `coerce` definition. The illegitimate `fmap` is of very little interest to me. Someone who cares about preserving their map count or whatever just won't be able to use `Functor` deriving for types explicitly mentioning their bogus one. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13328#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13328: Foldable, Functor, and Traversable deriving handle phantom types badly -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: deriving-perf Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott):
The question about `fmap` strictness looks like a red herring to me. There's no real difference between the empty case definition and the `coerce` definition.
Sure, I just wanted to note the "conflict".
The illegitimate `fmap` is of very little interest to me. Someone who cares about preserving their map count or whatever just won't be able to use `Functor` deriving for types explicitly mentioning their bogus one.
That's also fine, just make sure we note this if this gets implemented. Luckily, `Functor`/`Foldable`/`Traversable` happen to be pretty rigid, law-abiding classes, so this restriction won't really hurt anyone in practice. What is your opinion on the `RoleAnnotations` example above? This is the only thing that genuinely concerns me, since I think having the strictness of a derived `Foldable` instance change depending on whether a type parameter is phantom or non-phantom is quite unintuitive. I'm not sure of a good workaround, however. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13328#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13328: Foldable, Functor, and Traversable deriving handle phantom types badly -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: deriving-perf Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): The role annotation should (I believe) only affect instances derived outside the module. So I believe the concern would be for a type that is defined ''using'' a type defined in another module that has a role annotation. But again, that matches the "what the user would likely write by hand" scenario: we can only do as well as the user could. Yes, it's true that this introduces some potential for surprises; the user won't get a nice error message when they make the change. Do you think this is a judgement call that should be made through the proposal process? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13328#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13328: Foldable, Functor, and Traversable deriving handle phantom types badly -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: deriving-perf Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Sadly, a role annotation would affect the datatype even in the module in which it is originally defined: {{{#!hs {-# LANGUAGE RoleAnnotations, TemplateHaskell #-} import Language.Haskell.TH type role Foo nominal data Foo a = Foo a $(return []) main :: IO () main = putStrLn $(reifyRoles ''Foo >>= stringE . show) }}} {{{ $ runghc Bug.hs [NominalR] }}} The issue is really that role annotations are only a crude approximation of the property we actually want here. For `Functor` and `Traversable`, we really are using `coerce`, so a phantom role annotation is precisely what you need. But we aren't using `coerce` in the proposed `Foldable` instance, and moreover, the property we really want to ensure is that the type parameter doesn't appear anywhere in any constructor's fields. Sadly, a phantom role does not always imply this. I'm tempted to suggest a workaround in which we re-infer the roles for every data type, but this time, we ignore all user-supplied role annotations. That way, we would get precisely the right information about whether the last type parameter appears somewhere in the datatype's definition. But sadly, this would necessarily break abstraction in the case where a constructor's field mentions an abstract type that has been given a role annotation of representational or nominal. Another option we could choose is to simply skip over this optimization for `Foldable`. That's likely not what you'd prefer, but there are a number of properties which make dealing with `Foldable` awkward that aren't present with `Functor` and `Traversable`. In any event, presenting this idea via a proposal would certainly be a good thing. I'm curious to know what others think about this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13328#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13328: Foldable, Functor, and Traversable deriving handle phantom types badly -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: deriving-perf Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): You're right that the role is only an approximation for `Foldable`, but using that approximation has an important advantage: it ensures that deriving `foldMap` will never be worse than using `foldMapDefault` with a derived `Traversable` instance. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13328#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13328: Foldable, Functor, and Traversable deriving handle phantom types badly -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: deriving-perf Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): One way we could help mitigate the effect of this is by doing an additional optimization for derived `Foldable` instances. First, we check each constructor, and if it does not contain an occurrence of the last type parameter, we filter out that constructor. Then we generate the `foldMap` cases as normal for fhe constructors that remain, and if any constructors were filtered out, we generate a catch-all `foldMap _ _ = mempty` case at the end. This should at least help in the case when all the data constructors of a phantom type are in scope, but its role has been annotated as something other than phantom. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13328#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13328: Foldable, Functor, and Traversable deriving handle phantom types badly
-------------------------------------+-------------------------------------
Reporter: dfeuer | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.4.1
Component: Compiler | Version: 8.1
Resolution: | Keywords: deriving-perf
Operating System: Unknown/Multiple | Architecture:
Type of failure: Runtime | Unknown/Multiple
performance bug | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by David Feuer

#13328: Foldable, Functor, and Traversable deriving handle phantom types badly -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.1 Resolution: fixed | Keywords: deriving-perf Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * status: new => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13328#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC