[GHC] #15499: Panic in occurence analysis phase (?), getRuntimeRep

GHC ghc-devs at haskell.org
Thu Aug 9 22:47:13 UTC 2018


#15499: Panic in occurence analysis phase (?), getRuntimeRep
-------------------------------------+-------------------------------------
           Reporter:  _deepfire      |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  high           |         Milestone:  8.4.4
          Component:  Compiler       |           Version:  8.4.3
           Keywords:                 |  Operating System:  Linux
       Architecture:                 |   Type of failure:  Compile-time
  Unknown/Multiple                   |  crash or panic
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 Compiling this:

 {{{#!hs
 {-# LANGUAGE DataKinds, GADTs, KindSignatures #-}
 module Holo ()
 where

 data ADT (p :: Integer) where
   ADT ::
     { a :: a
     , b :: Integer
     } -> ADT p

 foo = undefined {b=undefined}
 }}}

 ..yields:
 {{{
 ghc: panic! (the 'impossible' happened)
   (GHC version 8.4.3 for x86_64-unknown-linux):
         getRuntimeRep
   p_a29z :: Integer
   Call stack:
       CallStack (from HasCallStack):
         callStackDoc, called at compiler/utils/Outputable.hs:1150:37 in
 ghc:Outputable
         pprPanic, called at compiler/types/Type.hs:1967:18 in ghc:Type

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

 -v4 suggests this happend during the occurence analysis phase (log
 attached).

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


More information about the ghc-tickets mailing list