[GHC] #9071: Panic with -XDeriveFunctor when deriving from a non-Functor in a separate module

#9071: Panic with -XDeriveFunctor when deriving from a non-Functor in a separate module -----------------------------------+--------------------------------------- Reporter: bens | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time crash Unknown/Multiple | Test Case: Difficulty: Unknown | Blocking: Blocked By: | Related Tickets: | -----------------------------------+--------------------------------------- == Mu in the same file == ''src/Main.hs'' {{{ {-# LANGUAGE DeriveFunctor #-} module Main where newtype Mu f = Mu (f (Mu f)) newtype K a b = K a newtype F a = F (Mu (K a)) deriving Functor main :: IO () main = return () }}} ---- {{{ $ cabal build Building panic-0.1.0.0... Preprocessing executable 'panic' for panic-0.1.0.0... [1 of 1] Compiling Main ( src/Main.hs, dist/build/panic/panic- tmp/Main.o ) src/Main.hs:7:37: No instance for (Functor Mu) arising from the first field of ‘F’ (type ‘Mu (K a)’) Possible fix: use a standalone 'deriving instance' declaration, so you can specify the instance context yourself When deriving the instance for (Functor F) }}} == Mu in a separate file == ''src/Mu.hs'' {{{ module Mu where newtype Mu f = Mu (f (Mu f)) }}} ''src/Main.hs'' {{{ {-# LANGUAGE DeriveFunctor #-} module Main where import Mu newtype K a b = K a newtype F a = F (Mu (K a)) deriving Functor main :: IO () main = return () }}} ---- {{{ $ cabal build Building panic-0.1.0.0... Preprocessing executable 'panic' for panic-0.1.0.0... [1 of 2] Compiling Mu ( src/Mu.hs, dist/build/panic/panic- tmp/Mu.o ) [2 of 2] Compiling Main ( src/Main.hs, dist/build/panic/panic- tmp/Main.o ) src/Main.hs:8:37:ghc: panic! (the 'impossible' happened) (GHC version 7.8.2 for x86_64-unknown-linux): Prelude.(!!): index too large Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9071 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9071: Panic with -XDeriveFunctor when deriving from a non-Functor in a separate module ---------------------------------------+----------------------------------- Reporter: bens | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time crash | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: ---------------------------------------+----------------------------------- Comment (by bens): It also crashes when running ghc directly, as in `ghc --make -isrc src/Main.hs` with any level of optimisation. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9071#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9071: Panic with -XDeriveFunctor when deriving from a non-Functor in a separate module ---------------------------------------+----------------------------------- Reporter: bens | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time crash | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: ---------------------------------------+----------------------------------- Changes (by bens): * cc: ben.d.sinclair@… (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9071#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9071: Panic with -XDeriveFunctor when deriving from a non-Functor in a separate module ---------------------------------------+----------------------------------- Reporter: bens | Owner: simonpj Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time crash | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: ---------------------------------------+----------------------------------- Changes (by simonpj): * owner: => simonpj Comment: Ugh. Good catch. Fixing. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9071#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9071: Panic with -XDeriveFunctor when deriving from a non-Functor in a separate
module
---------------------------------------+-----------------------------------
Reporter: bens | Owner: simonpj
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.8.2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time crash | Unknown/Multiple
Test Case: | Difficulty: Unknown
Blocking: | Blocked By:
| Related Tickets:
---------------------------------------+-----------------------------------
Comment (by Simon Peyton Jones

#9071: Panic with -XDeriveFunctor when deriving from a non-Functor in a separate
module
---------------------------------------+-----------------------------------
Reporter: bens | Owner: simonpj
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.8.2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time crash | Unknown/Multiple
Test Case: | Difficulty: Unknown
Blocking: | Blocked By:
| Related Tickets:
---------------------------------------+-----------------------------------
Comment (by Simon Peyton Jones

#9071: Panic with -XDeriveFunctor when deriving from a non-Functor in a separate module -------------------------------------------------+------------------------- Reporter: bens | Owner: Type: bug | simonpj Priority: normal | Status: merge Component: Compiler | Milestone: Resolution: | Version: 7.8.2 Operating System: Unknown/Multiple | Keywords: Type of failure: Compile-time crash | Architecture: Test Case: deriving/should_fail/T9071, | Unknown/Multiple T9071_2 | Difficulty: Blocking: | Unknown | Blocked By: | Related Tickets: -------------------------------------------------+------------------------- Changes (by simonpj): * status: new => merge * testcase: => deriving/should_fail/T9071, T9071_2 Comment: Fixed. Please merge to 7.8 branch. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9071#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9071: Panic with -XDeriveFunctor when deriving from a non-Functor in a separate module -------------------------------------------------+------------------------- Reporter: bens | Owner: Type: bug | simonpj Priority: normal | Status: Component: Compiler | closed Resolution: fixed | Milestone: 7.8.3 Operating System: Unknown/Multiple | Version: 7.8.2 Type of failure: Compile-time crash | Keywords: Test Case: deriving/should_fail/T9071, | Architecture: T9071_2 | Unknown/Multiple Blocking: | Difficulty: | Unknown | Blocked By: | Related Tickets: -------------------------------------------------+------------------------- Changes (by thoughtpolice): * status: merge => closed * resolution: => fixed Comment: Merged into 7.8.3. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9071#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9071: Panic with -XDeriveFunctor when deriving from a non-Functor in a separate module -------------------------------------------------+------------------------- Reporter: bens | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.8.3 Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time crash | Unknown/Multiple Test Case: deriving/should_fail/T9071, | Difficulty: T9071_2 | Unknown Blocking: | Blocked By: | Related Tickets: -------------------------------------------------+------------------------- Changes (by rwbarton): * owner: simonpj => * status: closed => new * resolution: fixed => Comment: There's some leftover debugging output in compiler/typecheck/TcRnTypes.lhs. Reopening so that it can be fixed and merged into 7.8.3. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9071#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9071: Panic with -XDeriveFunctor when deriving from a non-Functor in a separate module -------------------------------------------------+------------------------- Reporter: bens | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.8.3 Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time crash | Unknown/Multiple Test Case: deriving/should_fail/T9071, | Difficulty: T9071_2 | Unknown Blocking: | Blocked By: | Related Tickets: -------------------------------------------------+------------------------- Comment (by simonpj): Reid, thanks. Can you identify the "leftover debugging output" and/or offer a patch? Ta Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9071#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9071: Panic with -XDeriveFunctor when deriving from a non-Functor in a separate
module
-------------------------------------------------+-------------------------
Reporter: bens | Owner:
Type: bug | Status: new
Priority: normal | Milestone: 7.8.3
Component: Compiler | Version: 7.8.2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time crash | Unknown/Multiple
Test Case: deriving/should_fail/T9071, | Difficulty:
T9071_2 | Unknown
Blocking: | Blocked By:
| Related Tickets:
-------------------------------------------------+-------------------------
Comment (by Reid Barton

#9071: Panic with -XDeriveFunctor when deriving from a non-Functor in a separate module -------------------------------------------------+------------------------- Reporter: bens | Owner: Type: bug | Status: merge Priority: normal | Milestone: 7.8.3 Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time crash | Unknown/Multiple Test Case: deriving/should_fail/T9071, | Difficulty: T9071_2 | Unknown Blocking: | Blocked By: | Related Tickets: -------------------------------------------------+------------------------- Changes (by rwbarton): * status: new => merge -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9071#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9071: Panic with -XDeriveFunctor when deriving from a non-Functor in a separate module -------------------------------------------------+------------------------- Reporter: bens | Owner: Type: bug | Status: Priority: normal | closed Component: Compiler | Milestone: 7.8.3 Resolution: fixed | Version: 7.8.2 Operating System: Unknown/Multiple | Keywords: Type of failure: Compile-time crash | Architecture: Test Case: deriving/should_fail/T9071, | Unknown/Multiple T9071_2 | Difficulty: Blocking: | Unknown | Blocked By: | Related Tickets: -------------------------------------------------+------------------------- Changes (by thoughtpolice): * status: merge => closed * resolution: => fixed Comment: This was actually merged and I missed it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9071#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC