[GHC] #7729: GHC panics. Invalid core
GHC
cvs-ghc at haskell.org
Fri Mar 1 17:15:07 CET 2013
#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
More information about the ghc-tickets
mailing list