[GHC] #7611: Rewrite rules application prevented by type variable application (map id vs. map (\x -> x))

GHC cvs-ghc at haskell.org
Sun Feb 24 02:43:03 CET 2013


#7611: Rewrite rules application prevented by type variable application (map id
vs. map (\x -> x))
------------------------------------+---------------------------------------
Reporter:  nomeata                  |          Owner:                  
    Type:  bug                      |         Status:  new             
Priority:  normal                   |      Component:  Compiler        
 Version:  7.6.2                    |       Keywords:                  
      Os:  Unknown/Multiple         |   Architecture:  Unknown/Multiple
 Failure:  Runtime performance bug  |      Blockedby:                  
Blocking:                           |        Related:                  
------------------------------------+---------------------------------------
Changes (by liyang):

  * failure:  None/Unknown => Runtime performance bug
  * version:  7.6.1 => 7.6.2


Comment:

 I think this may be related, but in this case I can't see what rule I
 could possibly write that would fire:

 {{{
 {-# LANGUAGE TypeFamilies #-}
 type family Unit a :: *
 type instance Unit Integer = ()

 {-# INLINE [1] int #-}
 {-# RULES "int" int = fromInteger :: Integer -> Int #-}

 -- int :: (Integral i, Unit i ~ ()) => i -> Int -- doesn't fire
 int :: (Integral i) => i -> Int -- fires
 int = fromIntegral
 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/7611#comment:4>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler



More information about the ghc-tickets mailing list