[GHC] #8142: Panic on TypeFamilies compile

#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

#8142: Panic on TypeFamilies compile ---------------------------------------+----------------------------------- Reporter: zenzike | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: MacOS X | Architecture: Type of failure: Compile-time crash | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: ---------------------------------------+----------------------------------- Comment (by dreixel): Seems to be fixed in HEAD: {{{ Test.hs:6:18: Couldn't match type ‛Nu f0’ with ‛Nu f’ NB: ‛Nu’ is a type function, and may not be injective The type variable ‛f0’ is ambiguous Expected type: a -> Nu f Actual type: a -> Nu f0 When checking that ‛h’ has the inferred type ‛forall (f :: * -> *) a. a -> Nu f’ Probable cause: the inferred type is ambiguous In an equation for ‛tracer’: tracer = h where h = (\ (_, b) -> ((outI . fmap h) b)) . out Test.hs:6:57: Occurs check: cannot construct the infinite type: a ~ f1 a Expected type: a -> (t0, f1 a) Actual type: Nu ((,) t0) -> (t0, Nu ((,) t0)) Relevant bindings include h :: a -> Nu f1 (bound at Test.hs:6:18) In the second argument of ‛(.)’, namely ‛out’ In the expression: (\ (_, b) -> ((outI . fmap h) b)) . out }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8142#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8142: Panic on TypeFamilies compile ---------------------------------------+----------------------------------- Reporter: zenzike | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: MacOS X | Architecture: Type of failure: Compile-time crash | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: ---------------------------------------+----------------------------------- Comment (by jstolarek): Is this the same as #7729? I think we could add that program as yet another test to the testsuite. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8142#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8142: Panic on TypeFamilies compile ---------------------------------------+----------------------------------- Reporter: zenzike | Owner: jstolarek Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: MacOS X | Architecture: Type of failure: Compile-time crash | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: ---------------------------------------+----------------------------------- Changes (by jstolarek): * owner: => jstolarek -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8142#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8142: Panic on TypeFamilies compile
---------------------------------------+-----------------------------------
Reporter: zenzike | Owner: jstolarek
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.6.3
Resolution: | Keywords:
Operating System: MacOS X | Architecture:
Type of failure: Compile-time crash | Unknown/Multiple
Test Case: | Difficulty: Unknown
Blocking: | Blocked By:
| Related Tickets:
---------------------------------------+-----------------------------------
Comment (by Jan Stolarek

#8142: Panic on TypeFamilies compile -------------------------------------------------+------------------------- Reporter: zenzike | Owner: Type: bug | jstolarek Priority: normal | Status: Component: Compiler | closed Resolution: fixed | Milestone: Operating System: MacOS X | Version: 7.6.3 Type of failure: Compile-time crash | Keywords: Test Case: | Architecture: typecheck/should_fail/T8142.hs | Unknown/Multiple Blocking: | Difficulty: | Unknown | Blocked By: | Related Tickets: -------------------------------------------------+------------------------- Changes (by jstolarek): * status: new => closed * testcase: => typecheck/should_fail/T8142.hs * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8142#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC