[GHC] #11643: Core lint error in simplifier when compiling Rules1 with -O -prof -dcore-lint

GHC ghc-devs at haskell.org
Thu Feb 25 17:36:14 UTC 2016


#11643: Core lint error in simplifier when compiling Rules1 with -O -prof -dcore-
lint
-------------------------------------+-------------------------------------
           Reporter:  thomie         |             Owner:
               Type:  bug            |            Status:  new
           Priority:  highest        |         Milestone:  8.0.1
          Component:  Compiler       |           Version:  8.0.1-rc2
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 Running `make TEST=Rules1 WAY=profasm` results in a core lint error (see
 attachment) with ghc-8.0.1-rc2.

 This is the code:
 {{{#!hs
 {-# LANGUAGE TypeFamilies #-}

 module Rules1 where

 class C a where
   data T a

 instance (C a, C b) => C (a,b) where
   data T (a,b) = TPair (T a) (T b)

 mapT :: (C a, C b) => (a -> b) -> T a -> T b
 {-# NOINLINE mapT #-}  -- Otherwwise we get a warning from the rule
 mapT = undefined

 zipT :: (C a, C b) => T a -> T b -> T (a,b)
 {-# NOINLINE [1] zipT #-}
 zipT = undefined

 {-# RULES

 "zipT/mapT" forall f x y.
   zipT (mapT f x) y = mapT (\(x,y) -> (f x, y)) (zipT x y)

  #-}
 }}}

 {{{
 $ ghc-8.0.1 -O -prof Rules1.hs -dcore-lint
 }}}

 This is a regression from 7.10.3, and core lint errors are bad, so setting
 priority to highest.

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11643>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list