[GHC] #15709: GHC panic using TypeInType with minimal source code

GHC ghc-devs at haskell.org
Fri Oct 5 14:53:53 UTC 2018


#15709: GHC panic using TypeInType with minimal source code
-------------------------------------+-------------------------------------
           Reporter:  jnape          |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.4.3
           Keywords:  TypeInType     |  Operating System:  Linux
       Architecture:  x86_64         |   Type of failure:  Compile-time
  (amd64)                            |  crash or panic
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 The following source code causes GHC 8.4.3 on 64bit Linux to panic:

 {{{#!haskell
 {-# LANGUAGE TypeInType #-}

 module Lib where

 import Data.Kind

 class Contravariant f where
     contramap :: (a -> b) -> f b -> f a

 dimap :: (Contravariant (p :: * -> b -> p * b), Functor (p a)) => (z -> a)
 -> (b -> c) -> p a b -> p z c
 dimap f g = contramap f . fmap g
 }}}

 I have no idea if it should compile or not, but it shouldn't do this:

 {{{
 ghc: panic! (the 'impossible' happened)
   (GHC version 8.4.3 for x86_64-unknown-linux):
         piResultTy
   k_a34u[tau:1]
   *
   Call stack:
       CallStack (from HasCallStack):
         callStackDoc, called at compiler/utils/Outputable.hs:1150:37 in
 ghc:Outputable
         pprPanic, called at compiler/types/Type.hs:947:35 in ghc:Type

 Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
 }}}

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15709>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list