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

GHC ghc-devs at haskell.org
Sat May 3 16:59:45 UTC 2014


#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


More information about the ghc-tickets mailing list