[GHC] #8767: Add rules involving `coerce` to the libraries

#8767: Add rules involving `coerce` to the libraries ------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: task | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.9 Keywords: | Operating System: Unknown/Multiple Architecture: Unknown/Multiple | Type of failure: None/Unknown Difficulty: Unknown | Test Case: Blocked By: 8718 | Blocking: Related Tickets: #2110 | ------------------------------------+------------------------------------- With #2110 fixed, we can now add rules like {{{ {-# RULES "map/coerce" [0] map coerce = coerce #-} }}} to the standard libraries. But probably this should happen together or after #8718. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8767 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8767: Add rules involving `coerce` to the libraries
-------------------------------------+------------------------------------
Reporter: nomeata | Owner:
Type: task | Status: new
Priority: normal | Milestone:
Component: libraries/base | Version: 7.9
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture: Unknown/Multiple
Type of failure: None/Unknown | Difficulty: Unknown
Test Case: | Blocked By: 8718
Blocking: | Related Tickets: #2110
-------------------------------------+------------------------------------
Comment (by Austin Seipp

#8767: Add rules involving `coerce` to the libraries -------------------------------------+------------------------------------ Reporter: nomeata | Owner: Type: task | Status: merge Priority: normal | Milestone: 7.8.1 Component: libraries/base | Version: 7.8.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: 8718 Blocking: | Related Tickets: #2110 -------------------------------------+------------------------------------ Changes (by thoughtpolice): * cc: hvr (added) * status: new => merge * version: 7.9 => 7.8.1-rc2 * milestone: => 7.8.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8767#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8767: Add rules involving `coerce` to the libraries -------------------------------------------------+------------------------- Reporter: nomeata | Owner: Type: task | Status: merge Priority: normal | Milestone: 7.8.1 Component: libraries/base | Version: Resolution: | 7.8.1-rc2 Operating System: Unknown/Multiple | Keywords: Type of failure: None/Unknown | Architecture: Test Case: | Unknown/Multiple tests/simplCore/should_run/T2110.hs | Difficulty: Blocking: | Unknown | Blocked By: 8718 | Related Tickets: #2110 -------------------------------------------------+------------------------- Changes (by thoughtpolice): * testcase: => tests/simplCore/should_run/T2110.hs -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8767#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8767: Add rules involving `coerce` to the libraries -------------------------------------------------+------------------------- Reporter: nomeata | Owner: Type: task | Status: merge Priority: normal | Milestone: 7.8.1 Component: libraries/base | Version: Resolution: | 7.8.1-rc2 Operating System: Unknown/Multiple | Keywords: Type of failure: None/Unknown | Architecture: Test Case: | Unknown/Multiple tests/simplCore/should_run/T2110.hs | Difficulty: Blocking: | Unknown | Blocked By: 8718 | Related Tickets: #2110 -------------------------------------------------+------------------------- Comment (by thoughtpolice): Please excuse the completely stupid commit message. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8767#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8767: Add rules involving `coerce` to the libraries -------------------------------------------------+------------------------- Reporter: nomeata | Owner: Type: task | Status: merge Priority: normal | Milestone: 7.8.1 Component: libraries/base | Version: Resolution: | 7.8.1-rc2 Operating System: Unknown/Multiple | Keywords: Type of failure: None/Unknown | Architecture: Test Case: | Unknown/Multiple tests/simplCore/should_run/T2110.hs | Difficulty: Blocking: | Unknown | Blocked By: 8718 | Related Tickets: #2110 -------------------------------------------------+------------------------- Comment (by goldfire): But, there should be many more similar RULES than just this, no? For example, any lawful `Functor` instance should have a RULE for its `fmap`, as I understand. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8767#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8767: Add rules involving `coerce` to the libraries -------------------------------------------------+------------------------- Reporter: nomeata | Owner: Type: task | Status: merge Priority: normal | Milestone: 7.8.1 Component: libraries/base | Version: Resolution: | 7.8.1-rc2 Operating System: Unknown/Multiple | Keywords: Type of failure: None/Unknown | Architecture: Test Case: | Unknown/Multiple tests/simplCore/should_run/T2110.hs | Difficulty: Blocking: | Unknown | Blocked By: 8718 | Related Tickets: #2110 -------------------------------------------------+------------------------- Comment (by nomeata): I don’t think there is a point in merging this into 7.8; the support for `coerce` in rules was added to master after the freeze ([b4715d6] up to [cde88e2]). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8767#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8767: Add rules involving `coerce` to the libraries -------------------------------------------------+------------------------- Reporter: nomeata | Owner: Type: task | Status: Priority: normal | closed Component: libraries/base | Milestone: 7.8.1 Resolution: fixed | Version: Operating System: Unknown/Multiple | 7.8.1-rc2 Type of failure: None/Unknown | Keywords: Test Case: | Architecture: tests/simplCore/should_run/T2110.hs | Unknown/Multiple Blocking: | Difficulty: | Unknown | Blocked By: 8718 | Related Tickets: #2110 -------------------------------------------------+------------------------- Changes (by thoughtpolice): * status: merge => closed * resolution: => fixed Comment: Ah, I see. In that case that's fine - it's strictly an optimization, so I'm don't really care about missing this little thing. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8767#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8767: Add rules involving `coerce` to the libraries -------------------------------------------------+------------------------- Reporter: nomeata | Owner: Type: task | Status: new Priority: normal | Milestone: 7.8.1 Component: libraries/base | Version: Resolution: | 7.8.1-rc2 Operating System: Unknown/Multiple | Keywords: Type of failure: None/Unknown | Architecture: Test Case: | Unknown/Multiple tests/simplCore/should_run/T2110.hs | Difficulty: Blocking: | Unknown | Blocked By: 8718 | Related Tickets: #2110 -------------------------------------------------+------------------------- Changes (by thoughtpolice): * cc: ekmett (added) * status: closed => new * resolution: fixed => Comment: (Whoops, accidentally closed.) Richard, Edward probably has something to say about the `fmap` rule, but in general do we want it right now when it can break things? I'm under the impression there's not a sensible and safe one we can write that won't break for non-lawful Functors. (I guess we can tell everyone to always write ones that obey the rules, but I'm not sure how much that might backfire). There was some discussion of related approaches a few months ago around ICFP time (don't have a link on me). Anyway, worth a good discussion. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8767#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8767: Add rules involving `coerce` to the libraries -------------------------------------------------+------------------------- Reporter: nomeata | Owner: Type: task | Status: new Priority: normal | Milestone: 7.8.1 Component: libraries/base | Version: Resolution: | 7.8.1-rc2 Operating System: Unknown/Multiple | Keywords: Type of failure: None/Unknown | Architecture: Test Case: | Unknown/Multiple tests/simplCore/should_run/T2110.hs | Difficulty: Blocking: | Unknown | Blocked By: 8718 | Related Tickets: #2110 -------------------------------------------------+------------------------- Comment (by nomeata): I still believe that people should be free to write non-law-abiding instances (or maybe law-abiding up to some interface), and the compiler should not interfere with that. We should simply suggest them to add a `fmap coerce = coerce` rule for their particular fmap if they care. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8767#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8767: Add rules involving `coerce` to the libraries -------------------------------------------------+------------------------- Reporter: nomeata | Owner: Type: task | Status: new Priority: normal | Milestone: 7.8.1 Component: libraries/base | Version: Resolution: | 7.8.1-rc2 Operating System: Unknown/Multiple | Keywords: Type of failure: None/Unknown | Architecture: Test Case: | Unknown/Multiple tests/simplCore/should_run/T2110.hs | Difficulty: Blocking: | Unknown | Blocked By: 8718 | Related Tickets: #2110 -------------------------------------------------+------------------------- Comment (by ekmett): You can defintely have users write the rule for particular functors of course, but that means reasonably polymorphic code that is too complicated to INLINE will get penalized asymptotically, so in the long run I'd really like to find a better solution that might have a chance of firing on my code. ;) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8767#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8767: Add rules involving `coerce` to the libraries -------------------------------------------------+------------------------- Reporter: nomeata | Owner: Type: task | Status: new Priority: normal | Milestone: 7.8.1 Component: libraries/base | Version: Resolution: | 7.8.1-rc2 Operating System: Unknown/Multiple | Keywords: Type of failure: None/Unknown | Architecture: Test Case: | Unknown/Multiple tests/simplCore/should_run/T2110.hs | Difficulty: Blocking: | Unknown | Blocked By: 8718 | Related Tickets: #2110 -------------------------------------------------+------------------------- Comment (by goldfire): Right. I forgot that #2110 isn't getting into 7.8. Then, neither should this.... which is good, because I agree that maybe some more thought is required. I was ''not'' suggesting that there be a blanket `fmap coerce --> coerce` rule, just that we should add the specific rules for all the individual (lawful) `Functor`s that we define. I agree completely that users should be free to write unlawful `Functor`s if they wish to do so. I don't believe there's a link to earlier discussions on `fmap coerce` issue because the discussions happened among actual humans, in an actual room, instead of among computers online. It's an amazing thought. In any case, I remember one conclusion being a suggestion to add a new method to `Functor` being `fmapCoerce :: Coercible a b => f a -> f b`. This would have a default implementation of `fmapCoerce = fmap coerce` (no surprise there) but could be reimplemented where there would be a performance improvement. Returning to Edward's comment, I guess I don't understand the limits of the RULES mechanism to respond all that intelligently. In Core, anything that looks like `fmap coerce` in the source code would look something like `$fmapIdForSomeInstance <type parameters> (\x -> x |> co)`. This should be easy enough to match at the Core level. If it's impossible to write a RULE that desugars to the pattern above, then I think it's a bug (er, feature request) in the RULES mechanism, not a call for a change to the `Functor` definition. Though I'm not dead set against `fmapCoerce` in `Functor`, I believe that if we have to add such a thing, then there is a weakness in our design somewhere. During the conversations at ICFP, I was unaware of #2110 and Joachim's efforts to fix that bug. Now that we have that fixed, I believe `fmapCoerce` should be avoidable. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8767#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8767: Add rules involving `coerce` to the libraries -------------------------------------------------+------------------------- Reporter: nomeata | Owner: Type: task | Status: new Priority: normal | Milestone: 7.8.1 Component: libraries/base | Version: Resolution: | 7.8.1-rc2 Operating System: Unknown/Multiple | Keywords: Type of failure: None/Unknown | Architecture: Test Case: | Unknown/Multiple tests/simplCore/should_run/T2110.hs | Difficulty: Blocking: | Unknown | Blocked By: 8718 | Related Tickets: #2110 -------------------------------------------------+------------------------- Comment (by nomeata):
I was not suggesting that there be a blanket fmap coerce --> coerce rule, just that we should add the specific rules for all the individual (lawful) Functors that we define. I agree completely that users should be free to write unlawful Functors if they wish to do so.
Ok, good. Then we fully agree :-) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8767#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8767: Add rules involving `coerce` to the libraries -------------------------------------------------+------------------------- Reporter: nomeata | Owner: Type: task | Status: new Priority: normal | Milestone: 7.8.1 Component: libraries/base | Version: Resolution: | 7.8.1-rc2 Operating System: Unknown/Multiple | Keywords: Type of failure: None/Unknown | Architecture: Test Case: | Unknown/Multiple tests/simplCore/should_run/T2110.hs | Difficulty: Blocking: | Unknown | Blocked By: 8718 | Related Tickets: #2110 -------------------------------------------------+------------------------- Comment (by ekmett): The `fmapCoerce` solution turned out not to be powerful enough to handle things like `Compose f g` while `g` remains polymorphic or many monad transformers. We vacillated between a few other solutions that let you add a different member to Functor that could lift coercions by the end of ICFP, but with GHC 7.8 happening "any day now" at the time we agreed to just punt on it until we could give it due deliberation. My main point was that if the code is still polymorphic in the functor and complicated enough not to inline into a place where that rule can fire the rule doesn't help. We encourage people to write very polymorphic code. e.g. It solves many of the bugaboos people trot out about monad transformers and the like if you avoid picking a concrete instance until the last second. I'd be really sad to see that part of our culture die to get a few zero-cost newtype applications. Anyways, not sure what the right solution is yet, but I did want to interject that whatever it is, `fmapCoerce` isn't it. ;) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8767#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8767: Add rules involving `coerce` to the libraries -------------------------------------------------+------------------------- Reporter: nomeata | Owner: Type: task | Status: new Priority: normal | Milestone: 7.8.1 Component: libraries/base | Version: Resolution: | 7.8.1-rc2 Operating System: Unknown/Multiple | Keywords: Type of failure: None/Unknown | Architecture: Test Case: | Unknown/Multiple tests/simplCore/should_run/T2110.hs | Difficulty: Blocking: | Unknown | Blocked By: 8718 | Related Tickets: #2110 -------------------------------------------------+------------------------- Comment (by goldfire): Right -- of course. I guess I always am thinking that we have to know the `Functor` instance even to be thinking about any of this, because the `Functor` instance might not be lawful, in which case this optimization is bogus. But I do see how you might make progress with yet-to-be-imagined solution. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8767#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8767: Add rules involving `coerce` to the libraries -------------------------------------------------+------------------------- Reporter: nomeata | Owner: Type: task | Status: new Priority: normal | Milestone: 7.8.1 Component: libraries/base | Version: Resolution: | 7.8.1-rc2 Operating System: Unknown/Multiple | Keywords: Type of failure: None/Unknown | Architecture: Test Case: | Unknown/Multiple tests/simplCore/should_run/T2110.hs | Difficulty: Blocking: | Unknown | Blocked By: 8718 | Related Tickets: #2110 -------------------------------------------------+------------------------- Comment (by ekmett): That is why I think any solution that works in a polymorphic setting or one too big to `INLINE` really involves adding something to `Functor` that permits the lifting of coercions for lawful functors. `fmapCoerce` was the first such candidate. It just isn't strong enough. A more viable alternative is to add something like `liftCoercion :: Functor f => Coercion a b -> Maybe (Coercion (f a) (f b))` to `Functor`, analogous to the precedent of how `(<$)` is already added there to permit faster 'scrubbing' of functor contents with increased sharing. This'd permit `liftCoercion Coercion = Just Coercion` to be written (or generated) as a witness for the representational or phantom role of the argument, and it could be used inside an `fmapCoerce` to lift over complex polymorphic functors. There are admittedly a lot of moving parts in such a design, though, and even ''that'' design as I recall isn't sufficient to address more complicated transformers and recursive data types, so there is still work to be done. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8767#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8767: Add rules involving `coerce` to the libraries -------------------------------------------------+------------------------- Reporter: nomeata | Owner: Type: task | Status: new Priority: normal | Milestone: Component: libraries/base | 7.10.1 Resolution: | Version: 7.9 Operating System: Unknown/Multiple | Keywords: Type of failure: None/Unknown | Architecture: Test Case: | Unknown/Multiple tests/simplCore/should_run/T2110.hs | Difficulty: Blocking: | Unknown | Blocked By: 8718 | Related Tickets: #2110 -------------------------------------------------+------------------------- Changes (by thoughtpolice): * version: 7.8.1-rc2 => 7.9 * milestone: 7.8.1 => 7.10.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8767#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8767: Add rules involving `coerce` to the libraries -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: task | Status: new Priority: normal | Milestone: 7.10.1 Component: | Version: 7.9 libraries/base | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: 8718 Type of failure: | Related Tickets: #2110 None/Unknown | Test Case: | tests/simplCore/should_run/T2110.hs| Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by dmcclean): I'm out of my depth here, not even sure this thread is about what I'm running in to. I want to coerce from `f (Quantity d v)` to `f v` where `f` is a functor, so that I can add up all the values without their wrappers in the way and then wrap the answer. This works a charm if I specialize `f` to `[]`, but doesn't compile ("because 'f (Quantity d v)' and 'f v' are different types") in the polymorphic version. (Full function below.) {{{ sum :: forall f d v.(Num v, Foldable f, Functor f) => f (Quantity d v) -> Quantity d v sum = coerce . Data.Foldable.sum . (\x -> x :: f v) . coerce sum :: forall d v.(Num v) => [Quantity d v] -> Quantity d v sum = coerce . F.sum . (\x -> x :: [v]) . coerce }}} Is this thread about making a workaround for that? Is the reason that it's complicated because some functors have nominal roles? (Maybe a SortedList would break if you changed out `Ord` instances under it?) Or is there more to it than that? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8767#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8767: Add rules involving `coerce` to the libraries -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: task | Status: new Priority: normal | Milestone: 7.10.1 Component: | Version: 7.9 libraries/base | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: 8718 Type of failure: | Related Tickets: #2110 None/Unknown | Test Case: | tests/simplCore/should_run/T2110.hs| Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by nomeata):
Is this thread about making a workaround for that?
No. Or, not mainly.
Is the reason that it's complicated because some functors have nominal roles? (Maybe a SortedList would break if you changed out Ord instances under it?) Or is there more to it than that?
Precisely: We don’t know about the roles of type variables, so we cannot lift coercions through them. I believe that a subsequent design of the system that will be able to cope with Monad’s `join` might be able to handle that, but I’m not up on that. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8767#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8767: Add rules involving `coerce` to the libraries -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: task | Status: new Priority: normal | Milestone: 7.10.1 Component: | Version: 7.9 libraries/base | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: 8718 Type of failure: | Related Tickets: #2110 None/Unknown | Test Case: | tests/simplCore/should_run/T2110.hs| Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by dmcclean): Could the compiler always generate `(Functor f, Coercible a b) => Coercible f a -> Coercible f b` instances that magically either `fmap coerce` or `coerce` depending on the role of f's parameter? Wouldn't the concrete type of `f` be known by the time it came around to generating the instance? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8767#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8767: Add rules involving `coerce` to the libraries -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: task | Status: new Priority: normal | Milestone: 7.10.1 Component: | Version: 7.9 libraries/base | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: 8718 Type of failure: | Related Tickets: #2110 None/Unknown | Test Case: | tests/simplCore/should_run/T2110.hs| Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by ekmett): dmcclean: Note: such a `RULE` is predicated on your `Functor` actually being lawful as well as having a representational argument. (It'd also result in `Coercible (f a) (f b)`.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8767#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8767: Add rules involving `coerce` to the libraries -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: task | Status: new Priority: normal | Milestone: 7.10.1 Component: | Version: 7.9 libraries/base | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: 8718 Type of failure: | Related Tickets: #2110 None/Unknown | Test Case: | tests/simplCore/should_run/T2110.hs| Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by dmcclean): I knew about the representational parameter part, that's why I thought maybe it was possible to only generate the instance if `f` has a representational parameter. i.e. it's not one once-and-for-all instance for all functors, instead it's "magically" (as the current coercible instances are) generated once at each functor type with the branching between `fmap coerce` and `coerce` happening after considering the concrete type of `f`. The bit about the lawfulness I had missed. I don't understand how it results in `Coercible (f a) (f b)` with no context, even if it is once-and-for-all and not the magical akin-to-an- axiom-schema way, but I'm sure you're correct. It seems like the unlawful functor desideratum is very difficult to handle because we don't have a way to have a qualified type that is qualified by whether or not the `Functor` is lawful. One possible thing would be to have an {-# UNLAWFUL #-} pragma, and when you are magically generating instances you branch three ways instead of 2. (Possibly such a pragma could allow more aggressive optimizations in other cases too, with an opt out for 'criminals'?) 1) If the role is representational and there's no unlawful pragma, you generate `coerce`. 2) If there's no unlawful pragma, but the role is something other than representational you generate `fmap coerce`. 3) If there's an unlawful pragma, you generate `error "Attempt to coerce through unlawful functor Foo declared at line ..."`, on the grounds that `error` is not pretty, but neither is unlawfulness. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8767#comment:21 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8767: Add rules involving `coerce` to the libraries -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: task | Status: new Priority: normal | Milestone: 7.10.1 Component: | Version: 7.9 libraries/base | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: 8718 Type of failure: | Related Tickets: #2110 None/Unknown | Test Case: | tests/simplCore/should_run/T2110.hs| Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by goldfire): dmcclean: I think you want #9123. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8767#comment:22 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8767: Add rules involving `coerce` to the libraries
-------------------------------------+-------------------------------------
Reporter: nomeata | Owner: ekmett
Type: task | Status: new
Priority: normal | Milestone: 7.10.1
Component: Core | Version: 7.9
Libraries | Keywords:
Resolution: | Architecture: Unknown/Multiple
Operating System: | Difficulty: Unknown
Unknown/Multiple | Blocked By: 8718
Type of failure: | Related Tickets: #2110
None/Unknown |
Test Case: |
tests/simplCore/should_run/T2110.hs|
Blocking: |
Differential Revisions: |
-------------------------------------+-------------------------------------
Changes (by thomie):
* cc: dfeuer, core-libraries-committee@… (added)
Comment:
{{{
commit 603b7be7bd3abaf0e2c210e8d9015b1d613b4715
Author: David Feuer

#8767: Add rules involving `coerce` to the libraries -------------------------------------+------------------------------------- Reporter: nomeata | Owner: ekmett Type: task | Status: new Priority: normal | Milestone: 7.10.1 Component: Core | Version: 7.9 Libraries | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: 8718 Type of failure: | Related Tickets: #2110 None/Unknown | Test Case: | tests/simplCore/should_run/T2110.hs| Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by dfeuer): Replying to [comment:21 dmcclean]:
One possible thing would be to have an {-# UNLAWFUL #-} pragma, and when you are magically generating instances you branch three ways instead of 2. (Possibly such a pragma could allow more aggressive optimizations in other cases too, with an opt out for 'criminals'?)
I think it would make more sense to track `Functor` instances believed to be (sufficiently) lawful. A functor could be labeled `{-# LAWFUL #-}` in either `Unsafe` or `Trustworthy` modules, and any ''derived'' `Functor` instance without a `Functor` context could be treated as lawful as well. A functor labeled as `{-# LAWFUL #-}` could of course be lawful only up to some isomorphism; the pragma would declare that the instance won't break in any important way if the compiler relies on the functor laws. A similar mechanism could presumably be applied to other classes as well. Interaction with extreme polymorphism: to really take advantage, you'd presumably need to be able to express lawfulness in a context. So you'd need to be able to write something like {{{#!hs g :: ({-# LAWFUL #-} Functor f) => ... }}}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8767#comment:25 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8767: Add rules involving `coerce` to the libraries -------------------------------------+------------------------------------- Reporter: nomeata | Owner: ekmett Type: task | Status: new Priority: normal | Milestone: 7.12.1 Component: Core Libraries | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: 8718 | Test Case: Related Tickets: #2110 | tests/simplCore/should_run/T2110.hs | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by htebalaka): I'm a little out of my depth with rewrite rules, but is there anything preventing rules being associated with a typeclass? Then you could have zero method typeclasses like {{{ class Functor f => LawfulFunctor f where {-# RULES "fmap/coerce" fmap coerce = coerce #-} }}} and then any datatype that wants the rule just implements the typeclass, which is trivial. It would also address dfeuer's comment about lawfullness in constraints, though it would also generate a lot of noise in documentation (and might inherit the same issue with typeclasses that they can be hard to refactor). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8767#comment:27 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

I'm a little out of my depth with rewrite rules, but is there anything
#8767: Add rules involving `coerce` to the libraries -------------------------------------+------------------------------------- Reporter: nomeata | Owner: ekmett Type: task | Status: new Priority: normal | Milestone: 7.12.1 Component: Core Libraries | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: 8718 | Test Case: Related Tickets: #2110 | tests/simplCore/should_run/T2110.hs | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by dfeuer): Replying to [comment:27 htebalaka]: preventing rules being associated with a typeclass? Then you could have zero method typeclasses like
{{{ class Functor f => LawfulFunctor f where {-# RULES "fmap/coerce" fmap coerce = coerce #-} }}} and then any datatype that wants the rule just implements the typeclass, which is trivial. It would also address dfeuer's comment about lawfullness in constraints, though it would also generate a lot of noise in documentation (and might inherit the same issue with typeclasses that they can be hard to refactor).
I don't know too much about these things either, but I don't think this will work too well. The problem, as I understand it, is that the `LawfulFunctor` constraint has to be in place at the ''call site'', which will generally not be the case even when the functor is actually an instance of `LawfulFunctor`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8767#comment:28 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8767: Add rules involving `coerce` to the libraries -------------------------------------+------------------------------------- Reporter: nomeata | Owner: ekmett Type: task | Status: new Priority: normal | Milestone: 7.12.1 Component: Core Libraries | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | tests/simplCore/should_run/T2110.hs Blocked By: 8718 | Blocking: Related Tickets: #2110 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by nomeata): `Data.Map` already has rules for `map`, this [pull request](https://github.com/haskell/containers/pull/163) adds them for `mapKeysMonotonic`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8767#comment:29 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC