[GHC] #7729: GHC panics. Invalid core

GHC cvs-ghc at haskell.org
Sat Mar 9 21:16:18 CET 2013


#7729: GHC panics. Invalid core
-----------------------------------------------------+----------------------
  Reporter:  Khudyakov                               |          Owner:                  
      Type:  bug                                     |         Status:  closed          
  Priority:  normal                                  |      Milestone:                  
 Component:  Compiler                                |        Version:  7.6.2           
Resolution:  wontfix                                 |       Keywords:                  
        Os:  Unknown/Multiple                        |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown                            |     Difficulty:  Unknown         
  Testcase:  indexed_types/should_fail/T7729,T7729a  |      Blockedby:                  
  Blocking:                                          |        Related:                  
-----------------------------------------------------+----------------------
Changes (by ekmett):

 * cc: ekmett@… (added)


Comment:

 Had a user bitten by this one today:

 {{{
 {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, TypeFamilies #-}
 module Test where

 import Control.Lens

 newtype A a = A a deriving (Show)

 asA  :: Iso' a (A a)
 asA = iso A $ \(A x) -> x

 f :: (Ord a, Eq a) => a -> [(a,b)] -> Maybe b
 f _ _ = Nothing
 ‗‗
 type instance Index (A a) = a

 instance (Gettable f, Ord a) => Contains f (A a) where
   contains = containsLookup (\k m -> f k (m ^. from asA))

 thing :: A a
 thing = view asA []

 main = print $ thing ^. from asA
 }}}

 It causes

 {{{
 $ ghc --make Test.hs
 [1 of 1] Compiling A                ( Test.hs, Test.o )
 ghc: panic! (the 'impossible' happened)
   (GHC version 7.6.2 for x86_64-unknown-linux):
         cgLookupPanic (probably invalid Core; try -dcore-lint)
     $dMonadReader{v a2W4} [lid]
     static binds for:
     local binds for:

 Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
 }}}

 on 7.4.1 I get

 {{{
 localhost:wl-pprint-terminfo ekmett$ ghci ~/Cube.hs
 GHCi, version 7.4.1: http://www.haskell.org/ghc/  :? for help
 Loading package ghc-prim ... linking ... done.
 Loading package integer-gmp ... linking ... done.
 Loading package base ... linking ... done.

 /Users/ekmett/Cube.hs:17:14:
     Occurs check: cannot construct the infinite type: a3 = [(a3, a2)]
     Expected type: Index (A a) -> p Bool (f Bool) -> A a -> f (A a)
       Actual type: a3 -> p Bool (f Bool) -> A a -> f (A a)
     In the return type of a call of `containsLookup'
     In the expression: containsLookup (\ k m -> f k (m ^. from asA))
 }}}

 This http://hpaste.org/raw/83760 contains the result of {{{-dcore-lint}}}.

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



More information about the ghc-tickets mailing list