
#13929: GHC panic with levity polymorphism --------------------------------------+--------------------------------- Reporter: vagarenko | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Keywords: | Operating System: Windows Architecture: x86_64 (amd64) | Type of failure: None/Unknown Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: --------------------------------------+--------------------------------- I'm using GHC version 8.2.0.20170507 This code fails to compile {{{#!hs {-# LANGUAGE MagicHash #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE TypeInType #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE UnboxedTuples #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE AllowAmbiguousTypes #-} module Main where import GHC.Exts import Data.Kind import GHC.Generics class GUnbox (f :: Type -> Type) (r :: RuntimeRep) where type GUnboxed f r :: TYPE r gunbox :: f p -> GUnboxed f r instance (GUnbox f rf, GUnbox g rg) => GUnbox (f :*: g) ('TupleRep '[rf, rg]) where type GUnboxed (f :*: g) ('TupleRep '[rf, rg]) = (# GUnboxed f rf, GUnboxed g rg #) -- if I remove implementation of `gunbox` it compiles successfully gunbox (x :*: y) = (# gunbox x, gunbox y #) main :: IO () main = pure () }}} with message: {{{ [1 of 1] Compiling Main ( Main.hs, .stack- work\dist\f42fcbca\build\Main.o ) ghc.EXE: panic! (the 'impossible' happened) (GHC version 8.2.0.20170507 for x86_64-unknown-mingw32): isUnliftedType GUnboxed g_a21y rg_a21z :: TYPE rg_a21z Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler\utils\Outputable.hs:1134:58 in ghc:Outputable callStackDoc, called at compiler\utils\Outputable.hs:1138:37 in ghc:Outputable pprPanic, called at compiler\types\Type.hs:1954:10 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/13929 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler