[GHC] #7729: GHC panics. Invalid core

#7729: GHC panics. Invalid core -----------------------------+---------------------------------------------- Reporter: Khudyakov | Owner: Type: bug | Status: new Priority: normal | Component: Compiler Version: 7.6.2 | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Blockedby: Blocking: | Related: -----------------------------+---------------------------------------------- Following code snippet triggers panic: {{{ {-# LANGUAGE FlexibleContexts, TypeFamilies #-} module Monad where class Monad m => PrimMonad m where type PrimState m class MonadTrans t where lift :: Monad m => m a -> t m a class (PrimMonad (BasePrimMonad m), Monad m) => MonadPrim m where type BasePrimMonad m :: * -> * liftPrim :: BasePrimMonad m a -> m a newtype Rand m a = Rand { runRand :: Maybe (m ()) -> m a } instance (Monad m) => Monad (Rand m) where return = Rand . const . return (Rand rnd) >>= f = Rand $ \g -> (\x -> runRand (f x) g) =<< rnd g instance MonadTrans Rand where lift = Rand . const instance MonadPrim m => MonadPrim (Rand m) where type BasePrimMonad (Rand m) = BasePrimMonad m liftPrim = liftPrim . lift }}} GHC 7.6.2 panics {{{ $ ghc-7.6.2 -c Monad.hs ghc: panic! (the 'impossible' happened) (GHC version 7.6.2 for x86_64-unknown-linux): cgLookupPanic (probably invalid Core; try -dcore-lint) $dMonadTrans{v ahe} [lid] static binds for: local binds for: main:Monad.lift{v ra} [gid[ClassOp]] main:Monad.liftPrim{v rc} [gid[ClassOp]] main:Monad.$p1PrimMonad{v rgv} [gid[ClassOp]] main:Monad.$p1MonadPrim{v rgA} [gid[ClassOp]] main:Monad.$p2MonadPrim{v rgB} [gid[ClassOp]] Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} whereas 7.4.2 reports type error {{{ $ ghc-7.4.2 -c Monad.hs Monad.hs:28:14: Occurs check: cannot construct the infinite type: m0 = t0 m0 Expected type: BasePrimMonad (Rand m) a -> Rand m a Actual type: m0 a -> Rand m a In the expression: liftPrim . lift In an equation for `liftPrim': liftPrim = liftPrim . lift }}} -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7729 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7729: GHC panics. Invalid core ---------------------------------+------------------------------------------ Reporter: Khudyakov | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.2 Keywords: | Os: Unknown/Multiple Architecture: Unknown/Multiple | Failure: None/Unknown Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: | ---------------------------------+------------------------------------------ Changes (by simonpj): * difficulty: => Unknown Comment: Interesting. With HEAD we get {{{ T7729.hs:29:14: Could not deduce (BasePrimMonad (Rand m) ~ t0 (BasePrimMonad (Rand m))) from the context (PrimMonad (BasePrimMonad (Rand m)), Monad (Rand m), MonadPrim m) bound by the instance declaration at T7729.hs:26:10-42 The type variable ‛t0’ is ambiguous Expected type: t0 (BasePrimMonad (Rand m)) a -> Rand m a Actual type: BasePrimMonad (Rand m) a -> Rand m a Relevant bindings include liftPrim :: BasePrimMonad (Rand m) a -> Rand m a (bound at T7729.hs:29:3) In the first argument of ‛(.)’, namely ‛liftPrim’ In the expression: liftPrim . lift In an equation for ‛liftPrim’: liftPrim = liftPrim . lift }}} If you change the offending line to {{{ liftPrim x = liftPrim (lift x) }}} then we get a different erro rmessage {{{ Adding error: T7729.hs:28:31: Occurs check: cannot construct the infinite type: m0 ~ t0 m0 Expected type: m0 a Actual type: BasePrimMonad (Rand m) a In the first argument of ‛lift’, namely ‛x’ In the first argument of ‛liftPrim’, namely ‛(lift x)’ In the expression: liftPrim (lift x) }}} Although these errors look different, they are acutally pretty similar. GHC 7.6.2 fails to reject the program, but gives a Lint error if you use `-docore-lint`. I don't propose to try to fix this... too obscure. I'll add a regression test thought. Thank you for the example. Simon -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7729#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 simonpj): * status: new => closed * testcase: => indexed_types/should_fail/T7729,T7729a * resolution: => wontfix -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7729#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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

#7729: GHC panics. Invalid core -----------------------------------------------------+---------------------- Reporter: Khudyakov | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.6.3 Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Difficulty: Unknown Testcase: indexed_types/should_fail/T7729,T7729a | Blockedby: Blocking: | Related: -----------------------------------------------------+---------------------- Changes (by simonpj): * status: closed => new * resolution: wontfix => * milestone: => 7.6.3 Comment: Haev you checked whether it's fixed in HEAD, as this ticket claims? Currently it's a bit of a guess that it's the same bug, isn't it? It's bad that 7.6 fails here. I hate the idea of the main extant compiler being broken; very un-keen on tracking it down given that the benefit will be for a matter of months only. Well, I suppose the next HP is likely to use 7.6. It's a balance with how painful it is. Keep saying if it is! I think I'll re-open anyway. Simon -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7729#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7729: GHC panics. Invalid core -----------------------------------------------------+---------------------- Reporter: Khudyakov | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.6.3 Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Difficulty: Unknown Testcase: indexed_types/should_fail/T7729,T7729a | Blockedby: Blocking: | Related: -----------------------------------------------------+---------------------- Comment(by monoidal): For the record, I confirm that ekmett's program and the original ticket concerns exactly the same bug, fixed in HEAD. Both programs can be reduced to http://hpaste.org/88612, which crashes 7.6 and gives occurs check in 7.7. I don't think this bug is worth hunting and releasing another 7.6.x - I would close it. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7729#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7729: GHC panics. Invalid core -----------------------------------------------------+---------------------- Reporter: Khudyakov | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.6.3 Component: Compiler | Version: 7.6.2 Resolution: fixed | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Difficulty: Unknown Testcase: indexed_types/should_fail/T7729,T7729a | Blockedby: Blocking: | Related: -----------------------------------------------------+---------------------- Changes (by simonpj): * status: new => closed * resolution: => fixed Comment: OK, thanks for checking! Simon -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7729#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC