[GHC] #12834: GHC panic: while printing Non type-variable argument
GHC
ghc-devs at haskell.org
Sun Nov 13 14:04:27 UTC 2016
#12834: GHC panic: while printing Non type-variable argument
-------------------------------------+-------------------------------------
Reporter: phadej | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
{{{
{-# 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.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12834>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list