[GHC] #12630: Assertion failed with BuildFlavour = devel2

GHC ghc-devs at haskell.org
Tue Oct 25 00:08:19 UTC 2016


#12630: Assertion failed with  BuildFlavour = devel2
-------------------------------------+-------------------------------------
        Reporter:  pacak             |                Owner:
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  Compiler          |              Version:  8.0.1
      Resolution:                    |             Keywords:
Operating System:  Linux             |         Architecture:  x86_64
 Type of failure:  Compile-time      |  (amd64)
  crash                              |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by pacak):

 This code still triggers the issue in ghc-8.0 branch as of 24 Oct 2016,
 code above - no longer does that.

 {{{#!hs

 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE PolyKinds #-}


 module A where


 import GHC.Generics

 class Enum' f where
   enum' :: [f a]


 toEnumDefault :: (Generic a, Enum' (Rep a)) => Int -> a
 toEnumDefault i = let l = enum'
                   in if (length l > i)
                       then to (l !! i)
                        else error "toEnum: invalid index"

 class GEnum a
 }}}


 {{{
 [1 of 1] Compiling A                ( Generics/Deriving/Enum.hs,
 Generics/Deriving/Enum.o )
 ghc: panic! (the 'impossible' happened)
   (GHC version 8.0.1.20161022 for x86_64-unknown-linux):
         ASSERT failed!
   CallStack (from HasCallStack):
   assertPprPanic, called at compiler/types/TyCoRep.hs:2008:56 in
 ghc:TyCoRep
   checkValidSubst, called at compiler/types/TyCoRep.hs:2044:17 in
 ghc:TyCoRep
   substTy, called at compiler/types/TyCoRep.hs:1986:3 in ghc:TyCoRep
   in_scope InScope [a2Um :-> a_a2Um[sk], a2Ur :-> k_a2Ur[tau:3],
                     a2Us :-> f_a2Us[tau:3], a2Uu :-> a_a2Uu[sk]]
   tenv [a2Um :-> a_a2Uu[sk]]
   tenvFVs [a2Ui :-> k_a2Ui[tau:5], a2Uu :-> a_a2Uu[sk]]
   cenv []
   cenvFVs []
   tys [[f_a2Us[tau:3] a_a2Um[sk]]]
   cos []

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

 }}}

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


More information about the ghc-tickets mailing list