Re: [GHC] #7398: RULES don't apply to a newtype constructor

#7398: RULES don't apply to a newtype constructor -------------------------------------+------------------------------------- Reporter: shachaf | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 7.6.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #6082, #10418, | Differential Rev(s): #13290 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * milestone: => 8.6.1 Comment: I'm adding a milestone because I suspect we may have enough machinery to make this work . Consider this code: {{{#!hs import Data.Functor.Identity import Data.Coerce hello :: (a -> b) -> a -> b hello f x = f x {-# INLINE [1] hello #-} {-# RULES "not good" forall (f :: Identity a -> a) x. hello f (Identity x) = x "also bad" forall f (x :: a). hello f (Identity x :: Identity a) = x "yes good" forall (f :: Identity a -> a) x. hello f (coerce x) = x "also good" forall f (x :: a) . hello f (coerce x :: Identity a) = x "just fine" forall f (x :: a). hello f (coerce @a @(Identity a) x) = x #-} test :: (Identity a -> a) -> a -> a test f x = hello f (Identity x) {-# NOINLINE test #-} }}} The rule labeled "not good" doesn't fire, but the one labeled "yes good" fires. The only difference is the spelling of `coerce`! This seems to suggest that we can apply some of the machinery for `coerce` rules to sometimes make good things happen. In particular, it seems likely that after type checking the rule, we can simply replace each `newtype` constructor/accessor with an appropriately typed invocation of `coerce`, and make the rules engine work. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/7398#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC