[GHC] #14575: ghc: panic! (the 'impossible' happened)

GHC ghc-devs at haskell.org
Tue Dec 12 12:24:08 UTC 2017


#14575: ghc: panic! (the 'impossible' happened)
-------------------------------------+-------------------------------------
           Reporter:  Pauly          |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:  ⊥
          Component:  Compiler       |           Version:  8.0.2
           Keywords:  template       |  Operating System:  Linux
  haskell                            |
       Architecture:  x86_64         |   Type of failure:  GHC doesn't work
  (amd64)                            |  at all
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 I got:

     ghc: panic! (the 'impossible' happened)
       (GHC version 8.0.2 for x86_64-unknown-linux):
         initTc: unsolved constraints
       WC {wc_insol = [W] spec_a86Q :: t_a86P[tau:1] (CHoleCan: spec)}

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

 This happens after adding of this call in test file (called
 SimpleTaggingSpec.hs):

 {{{#!hs
 $(shrinkEnumTag AnyJT)
 }}}

 Implementation of this ''shrinkEnumTag'' looks:

 {{{#!hs
 shrinkEnumTag :: forall a. (Data a, IsTag a) => a -> Q [Dec]
 shrinkEnumTag enm = do
   let dt = dataTypeOf enm
       ty = mkName $ dataTypeName dt
       tickAdd = (++"'")
       nameWith f = mkName . f . show
       derivs' = ConT . mkName <$> ["Eq", "Ord", "Enum"]
       mkShow tn tn' =
         [d|instance Show $(conT tn') where
              show a = show $ (toEnum $ fromEnum a :: $(conT tn))|]
   AlgRep algCs <- pure $ dataTypeRep dt
   let algCs' = [mkName $ show c | c <- algCs, fromConstr c /= (anyTag::a)]
       newCs = [NormalC (nameWith tickAdd n) [] | n <- algCs']
   TyConI tyCon <- reify ty
   decs <- case tyCon of
     DataD _cxt _nm tyVars _mbKind _cs _derivs -> do
       let ty' = nameWith tickAdd ty
       when (null newCs) $ fail "Can't find normal constructors"
       showInst <- mkShow ty ty'
       return $ [DataD [] ty' tyVars Nothing newCs derivs'] ++ showInst
     _ -> fail "expected Enum-like data type"
   return decs
 }}}

 If I add this call in not-test module, all is good, compilation is fine,
 application works.
 I use GHC 8.0.2, this happened with LTS-8.13 and LTS-9.18. Project uses
 stack tool. OS is Linux OpenSUSE Tumbleweed. I updated stack to the last
 version  (1.6.1) but this did not help.

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


More information about the ghc-tickets mailing list