[GHC] #15625: GHC panic, with QuantifiedConstraints

GHC ghc-devs at haskell.org
Tue Sep 11 13:15:35 UTC 2018


#15625: GHC panic, with QuantifiedConstraints
-------------------------------------+-------------------------------------
        Reporter:  Iceland_jack      |                Owner:  (none)
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  Compiler          |              Version:  8.6.1-beta1
      Resolution:                    |             Keywords:
                                     |  QuantifiedConstraints
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by RyanGlScott):

 If you don't have a GHC build with `ASSERT`ions enabled, then it's worth
 noting that this program also triggers a Core Lint error:

 {{{
 $ /opt/ghc/8.6.1/bin/ghci Bug.hs -dcore-lint
 GHCi, version 8.6.0.20180907: http://www.haskell.org/ghc/  :? for help
 Loaded GHCi configuration from /home/ryanglscott/.ghci
 [1 of 1] Compiling Main             ( Bug.hs, interpreted )
 *** Core Lint errors : in result of Desugar (after optimization) ***
 <no location info>: warning:
     [in body of letrec with binders $dIP_a2KT :: HasCallStack]
     co_a2Lc :: a_a1Iw[sk:1] ~# 'KL Any
     [LclId[CoVarId]] is out of scope
 *** Offending Program ***

 <elided>

 ekki__
   :: forall (m :: * -> *) (a :: KL_kind m).
      (Monad m, forall xx. AsKL a xx) =>
      KLEISLI m a a
 [LclIdX]
 ekki__
   = \ (@ (m_a1Iv :: * -> *))
       (@ (a_a1Iw :: KL_kind m_a1Iv))
       _ [Occ=Dead]
       (df_a1Iz :: forall xx. AsKL a_a1Iw xx) ->
       case \ (@ xx_a1Fp) ->
              heq_sel
                @ (KL_kind m_a1Iv)
                @ (KL_kind m_a1Iv)
                @ a_a1Iw
                @ ('KL xx_a1Fp)
                ($p1~
                   @ (KL_kind m_a1Iv)
                   @ a_a1Iw
                   @ ('KL xx_a1Fp)
                   ($p1AsKL @ m_a1Iv @ a_a1Iw @ xx_a1Fp (df_a1Iz @
 xx_a1Fp)))
       of df_a2Lp
       { __DEFAULT ->
       let {
         $dIP_a2KT :: HasCallStack
         [LclId]
         $dIP_a2KT
           = (pushCallStack
                (unpackCString# "undefined"#,
                 SrcLoc
                   (unpackCString# "main"#)
                   (unpackCString# "Main"#)
                   (unpackCString# "Bug.hs"#)
                   (I# 16#)
                   (I# 20#)
                   (I# 16#)
                   (I# 29#))
                ((emptyCallStack
                  `cast` (Sym (N:IP[0] <"callStack">_N <CallStack>_N)
                          :: CallStack ~R# (?callStack::CallStack)))
                 `cast` (N:IP[0] <"callStack">_N <CallStack>_N
                         :: (?callStack::CallStack) ~R# CallStack)))
             `cast` (Sym (N:IP[0] <"callStack">_N <CallStack>_N)
                     :: CallStack ~R# (?callStack::CallStack)) } in
       (break<0>()
        $WMkKLEISLI
          @ Any
          @ m_a1Iv
          @ Any
          (undefined @ 'LiftedRep @ (Any -> m_a1Iv Any) $dIP_a2KT))
       `cast` ((KLEISLI <m_a1Iv>_N (Sym co_a2Lc) (Sym co_a2Lc))_R
               :: KLEISLI m_a1Iv ('KL Any) ('KL Any)
                  ~R# KLEISLI m_a1Iv a_a1Iw[sk:1] a_a1Iw[sk:1])
       }
 }}}

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


More information about the ghc-tickets mailing list