[GHC] #14735: GHC Panic with QuantifiedConstraints

GHC ghc-devs at haskell.org
Mon Jan 29 03:30:44 UTC 2018


#14735: GHC Panic with QuantifiedConstraints
-------------------------------------+-------------------------------------
           Reporter:  Iceland_jack   |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.2.2
           Keywords:                 |  Operating System:  Unknown/Multiple
  QuantifiedContexts                 |
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 From branch [https://ghc.haskell.org/trac/ghc/ticket/2893#comment:28
 wip/T2893]

 {{{#!hs
 {-# Language QuantifiedConstraints #-}
 {-# Language StandaloneDeriving #-}
 {-# Language DataKinds #-}
 {-# Language TypeOperators #-}
 {-# Language GADTs #-}
 {-# Language KindSignatures #-}
 {-# Language FlexibleInstances #-}
 {-# Language UndecidableInstances #-}
 {-# Language MultiParamTypeClasses #-}
 {-# Language RankNTypes #-}
 {-# Language ConstraintKinds #-}

 import Data.Kind

 data D c where
   D :: c => D c

 newtype a :- b = S (a => D b)

 class C1 a b
 class C2 a b
 instance C1 a b => C2 a b

 class    (forall xx. f xx) => Limit f
 instance (forall xx. f xx) => Limit f

 -- impl :: Limit (C1 a) :- Limit (C2 a)
 -- impl = S D

 infixr 5 :<
 data Sig a = N a | a :< Sig a

 data AST :: (Sig Type -> Type) -> (Sig Type -> Type) where
   Sym  :: dom a -> AST dom a
   (:$) :: AST dom (xx :< a) -> AST dom (N xx) -> AST dom a

 deriving instance (forall xx. Show (dom xx)) => Show (AST dom a)

 data Arith a where
   Plus :: Arith (Int :< Int :< N Int)

 deriving instance Show (Arith a)
 }}}

 loading this program and evaluating `Sym Plus` works fine:

 {{{
 $ ghc-stage2 --interactive hs/175-bug.hs
 GHCi, version 8.5.20180128: http://www.haskell.org/ghc/  :? for help
 [1 of 1] Compiling Main             ( hs/175-bug.hs, interpreted )
 Ok, one module loaded.
 *Main> Sym Plus
 Sym Plus
 *Main>
 }}}

 but we uncomment `impl` we get a panic!

 {{{
 GHCi, version 8.5.20180128: http://www.haskell.org/ghc/  :? for help
 [1 of 1] Compiling Main             ( hs/175-bug.hs, interpreted )
 Ok, one module loaded.
 *Main> Sym Plus
 ghc-stage2: panic! (the 'impossible' happened)
   (GHC version 8.5.20180128 for x86_64-unknown-linux):
         nameModule
   system df_a2VB
   Call stack:
       CallStack (from HasCallStack):
         callStackDoc, called at compiler/utils/Outputable.hs:1150:37 in
 ghc:Outputable
         pprPanic, called at compiler/basicTypes/Name.hs:241:3 in ghc:Name

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

 *Main>
 }}}

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


More information about the ghc-tickets mailing list