#5973: Rewrite rule not firing for typeclass
------------------------------+---------------------------------------------
Reporter: SamAnklesaria | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 7.4.1 | Keywords:
Os: Unknown/Multiple | Architecture: Unknown/Multiple
Failure: None/Unknown | Testcase:
Blockedby: | Blocking:
Related: |
------------------------------+---------------------------------------------
The following rewrite rule fires for a normal function, but fails to fire
as the method of a typeclass.
{{{
{-# OPTIONS_GHC -O -ddump-rule-firings #-}
module RewriteProblems where
{-# RULES
"rewrite/class" forall a. id1 (id1 a) = RDUnit
"rewrite/static" forall a. id1' (id1' a) = RDUnit
#-}
class Ider a where
id1 :: a -> a
data RewriteD = RDUnit
instance Ider RewriteD where
{-# INLINE[1] id1 #-}
id1 a = RDUnit
classTest :: RewriteD
classTest = id1 (id1 RDUnit)
staticTest :: RewriteD
staticTest = id1' (id1' RDUnit)
{-# INLINE[1] id1' #-}
id1' :: RewriteD -> RewriteD
id1' a = RDUnit
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5973>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs