GHC panic: while printing Non type-variable argument
{-# LANGUAGE GADTs, TypeFamilies, DataKinds, TypeOperators, MultiParamTypeClasses, UndecidableInstances, UndecidableSuperClasses, FlexibleInstances, PolyKinds, KindSignatures #-}
import GHC.Exts (Constraint)
newtype I a = I a
data NP :: (k -> *) -> [k] -> * where
Nil :: NP f '[]
(:*) :: f x -> NP f xs -> NP f (x ': xs)
infixr 5 :*
class (AllF f xs, SListI xs) => All (f :: k -> Constraint) (xs :: [k])
instance (AllF f xs, SListI xs) => All f xs
data SList :: [k] -> * where
SNil :: SList '[]
SCons :: SListI xs => SList (x ': xs)
class SListI (xs :: [k]) where
-- | Get hold of the explicit singleton (that one can then
-- pattern match on).
sList :: SList xs
instance SListI '[] where
sList = SNil
instance SListI xs => SListI (x ': xs) where
sList = SCons
-- | Type family used to implement 'All'.
--
type family AllF (c :: k -> Constraint) (xs :: [k]) :: Constraint
type instance AllF _c '[] = ()
type instance AllF c (x ': xs) = (c x, All c xs)
semigroup :: All ((~) (Maybe Int)) xs => NP I xs -> NP I xs -> NP I xs
semigroup = undefined
Causes
ghc-failure-all.hs:37:14: error:
• Non type-variable argumentghc: panic! (the 'impossible' happened)
(GHC version 8.0.1 for x86_64-apple-darwin):
print_equality ~
If AllF
is used directly in the definition of sappend
, there is no error whatsoever.
Trac metadata
Trac field | Value |
---|---|
Version | 8.0.1 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |