
#15966: panic when using RebindableSyntax -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.3 Component: Compiler | Version: 8.6.2 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: -------------------------------------+------------------------------------- https://gist.github.com/mpickering/216ecdd9d8766dce2ff1080a17f77a0e {{{ {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE InstanceSigs #-} {-# LANGUAGE RebindableSyntax #-} {-# OPTIONS_GHC -Wall -Wno-missing-signatures -Wno-unticked-promoted- constructors -Wno-name-shadowing -fwarn-partial-type-signatures -Wno- partial-type-signatures #-} module Repro(main) where import Prelude hiding (Monad(..)) import Control.Applicative data E (a :: * -> *) (n :: *) where VarE :: a n -> E a n instance IMonad E where return :: a n -> E a n return = VarE (>>=) :: E a n -> (forall n . a n -> E b n) -> E b n VarE x >>= f = f x class IMonad (m :: (* -> *) -> (* -> *)) where return :: forall a n . a n -> m a n (>>=) :: m a n -> (forall n . a n -> m b n) -> m b n one :: Const Int n one = (Const 1) example_4 :: E (Const Int) n example_4 = do x <- (return one) return x main = example_4 `seq` () }}} Compiling this file with GHC leads to a StgCmmEnv panic. {{{ ghc: panic! (the 'impossible' happened) (GHC version 8.6.2 for x86_64-unknown-linux): StgCmmEnv: variable not found $dIMonad_a1lY local binds for: return
= $tc'VarE $tcE $tcIMonad $trModule $tc'VarE1_r1oI $tc'VarE2_r1ps $krep_r1pt $krep1_r1pu $krep2_r1pv $krep3_r1pw $krep4_r1px $tcE1_r1py $tcE2_r1pz $tcIMonad1_r1pA $tcIMonad2_r1pB $krep5_r1pC $krep6_r1pD $krep7_r1pE $trModule1_r1pF $trModule2_r1pG $trModule3_r1pH $trModule4_r1pI $krep8_r1pJ $krep9_r1pK sat_s1rG Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler/utils/Outputable.hs:1160:37 in ghc:Outputable pprPanic, called at compiler/codeGen/StgCmmEnv.hs:149:9 in ghc:StgCmmEnv
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} Loading the file into GHCi succeeds but then when the `main` function is invoked, a `nameModule` panic occurs. {{{ *Repro> main ghc: panic! (the 'impossible' happened) (GHC version 8.6.2 for x86_64-unknown-linux): nameModule system $dIMonad_a1LV Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler/utils/Outputable.hs:1160:37 in ghc:Outputable pprPanic, called at compiler/basicTypes/Name.hs:240:3 in ghc:Name Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} Reproduced on 8.6.{2,1} 8.4.4 8.2.2 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15966 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler