
#8142: Panic on TypeFamilies compile -----------------------------------+--------------------------------------- Reporter: zenzike | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Keywords: | Operating System: MacOS X Architecture: | Type of failure: Compile-time crash Unknown/Multiple | Test Case: Difficulty: Unknown | Blocking: Blocked By: | Related Tickets: | -----------------------------------+--------------------------------------- The following code produces a panic: {{{
{-# LANGUAGE TypeFamilies #-}
module Bug where
tracer :: (Functor f, Coinductive f) => (c -> f c) -> (c -> f c) tracer = h where h = (\(_, b) -> ((outI . fmap h) b)) . out
class Functor g => Coinductive g where type Nu g :: * out :: Nu g -> g (Nu g) outI :: g (Nu g) -> Nu g }}} Compiling with ghc-7.6.3 gives: {{{ $ ghc Bug.lhs [1 of 1] Compiling Bug ( Bug.lhs, Bug.o ) ghc: panic! (the 'impossible' happened) (GHC version 7.6.3 for x86_64-apple-darwin): cgLookupPanic (probably invalid Core; try -dcore-lint) h{v aeN} [lid] static binds for: local binds for: main:Bug.outI{v r0} [gid[ClassOp]] main:Bug.out{v r1} [gid[ClassOp]] main:Bug.$p1Coinductive{v reT} [gid[ClassOp]]
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8142 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler