[GHC] #16135: Panic with ExistentialQuantification and ApplicativeDo

#16135: Panic with ExistentialQuantification and ApplicativeDo -------------------------------------+------------------------------------- Reporter: Ashley | Owner: (none) Yakeley | Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{ {-# LANGUAGE ExistentialQuantification, ApplicativeDo #-} module Bug where data T f = forall a. MkT (f a) runf :: forall f. Functor f => IO (T f) runf = do return () MkT fa <- runf return $ MkT fa }}} {{{ Bug.hs:11:18: error:ghc: panic! (the 'impossible' happened) (GHC version 8.6.3 for x86_64-unknown-linux): No skolem info: [a_a1nb[ssk:2]] Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler/utils/Outputable.hs:1160:37 in ghc:Outputable pprPanic, called at compiler/typecheck/TcErrors.hs:2891:5 in ghc:TcErrors Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16135 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16135: Panic with ExistentialQuantification and ApplicativeDo -------------------------------------+------------------------------------- Reporter: Ashley Yakeley | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by Ashley Yakeley: Old description:
{{{ {-# LANGUAGE ExistentialQuantification, ApplicativeDo #-}
module Bug where
data T f = forall a. MkT (f a)
runf :: forall f. Functor f => IO (T f) runf = do return () MkT fa <- runf return $ MkT fa }}}
{{{
Bug.hs:11:18: error:ghc: panic! (the 'impossible' happened) (GHC version 8.6.3 for x86_64-unknown-linux): No skolem info: [a_a1nb[ssk:2]] Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler/utils/Outputable.hs:1160:37 in ghc:Outputable pprPanic, called at compiler/typecheck/TcErrors.hs:2891:5 in ghc:TcErrors
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}}
New description: {{{#!hs {-# LANGUAGE ExistentialQuantification, ApplicativeDo #-} module Bug where data T f = forall a. MkT (f a) runf :: forall f. Functor f => IO (T f) runf = do return () MkT fa <- runf return $ MkT fa }}} {{{ Bug.hs:11:18: error:ghc: panic! (the 'impossible' happened) (GHC version 8.6.3 for x86_64-unknown-linux): No skolem info: [a_a1nb[ssk:2]] Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler/utils/Outputable.hs:1160:37 in ghc:Outputable pprPanic, called at compiler/typecheck/TcErrors.hs:2891:5 in ghc:TcErrors Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16135#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16135: Panic with ExistentialQuantification and ApplicativeDo -------------------------------------+------------------------------------- Reporter: Ashley Yakeley | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.3 Resolution: | Keywords: ApplicativeDo Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: => ApplicativeDo -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16135#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16135: Panic with ExistentialQuantification and ApplicativeDo -------------------------------------+------------------------------------- Reporter: Ashley Yakeley | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.3 Resolution: | Keywords: ApplicativeDo Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I think the root cause of this is that the applicative-do stuff just doesn't work well with existentials. See [https://www.microsoft.com/en- us/research/publication/desugaring-haskells-do-notation-into-applicative- operations/ the paper]. The desugaring in Fig 5 really only works if the binder of the patterns don't include existentials. To me that says: * GHC should check for this and complain if necessary. Not crash! * Someone might like to think about whether it'd be possible to accommodate existentials. Simon M: this is your territory. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16135#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC