
#13951: InScope set assertion failure from monad-skeleton -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 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 PolyKinds, GADTs, Rank2Types, ScopedTypeVariables, Trustworthy #-} module Control.Monad.Skeleton.Internal where data Cat k a b where Empty :: Cat k a a Leaf :: k a b -> Cat k a b Tree :: Cat k a b -> Cat k b c -> Cat k a c viewL :: forall k a b r. Cat k a b -> ((a ~ b) => r) -> (forall x. k a x -> Cat k x b -> r) -> r viewL Empty e _ = e viewL (Leaf k) _ r = k `r` Empty viewL (Tree a b) e r = go a b where go :: Cat k a x -> Cat k x b -> r go Empty t = viewL t e r go (Leaf k) t = r k t go (Tree c d) t = go c (Tree d t) }}} Leads to the assertion failure {{{ [1 of 1] Compiling Control.Monad.Skeleton.Internal ( Internal.hs, Internal.o ) WARNING: file compiler/simplCore/OccurAnal.hs, line 2160 Just 3 [] ghc: panic! (the 'impossible' happened) (GHC version 8.2.0.20170708 for x86_64-unknown-linux): ASSERT failed! in_scope InScope {x_avF ds_d14c} tenv [avF :-> x_avF] tenvFVs [avF :-> x_avF, a11Z :-> k_a11Z] cenv [] cenvFVs [] tys [k1_a120 a_a121 x_avF] cos [] Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1133:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1188:22 in ghc:Outputable assertPprPanic, called at compiler/types/TyCoRep.hs:2088:56 in ghc:TyCoRep checkValidSubst, called at compiler/types/TyCoRep.hs:2121:29 in ghc:TyCoRep substTy, called at compiler/coreSyn/CoreArity.hs:1197:19 in ghc:CoreArity Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1133:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1137:37 in ghc:Outputable pprPanic, called at compiler/utils/Outputable.hs:1186:5 in ghc:Outputable assertPprPanic, called at compiler/types/TyCoRep.hs:2088:56 in ghc:TyCoRep checkValidSubst, called at compiler/types/TyCoRep.hs:2121:29 in ghc:TyCoRep substTy, called at compiler/coreSyn/CoreArity.hs:1197:19 in ghc:CoreArity Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13951 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler