[GHC] #11184: panic tcMonoExpr _ with bad indentation in TH code

#11184: panic tcMonoExpr _ with bad indentation in TH code -------------------------------------+------------------------------------- Reporter: TeroLaitinen | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Runtime crash Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs {-# LANGUAGE TemplateHaskell #-} import Data.Aeson.TH data Record = Record { type_ :: Int } $(deriveJSON defaultOptions{ fieldLabelModifier = \x -> case x of "type_" -> "type" _ -> x } ''Record) }}} gives {{{ ghc: panic! (the 'impossible' happened) (GHC version 7.10.2 for x86_64-unknown-linux): tcMonoExpr _ }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11184 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11184: panic tcMonoExpr _ with bad indentation in TH code -------------------------------------+------------------------------------- Reporter: TeroLaitinen | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by phadej): This happens because some "grammar" checks happen after the parsing phase: This fails with parse error: {{{ foo = \x -> case x of "foo" -> "bar" _ -> x {- bar.hs:32:21: parse error on input ‘->’ -} }}} But this, which is triggered in TH slice, is something different: {{{ foo = (\x -> case x of "foo" -> "bar" _ -> x) {- bar.hs:20:8: Pattern syntax in expression context: \ x -> case x of { "foo" -> "bar" (...) } -> x -} }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11184#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11184: panic tcMonoExpr _ with bad indentation in TH code -------------------------------------+------------------------------------- Reporter: TeroLaitinen | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by phadej): Also happens with latest HEAD {{{ ghc-stage2: panic! (the 'impossible' happened) (GHC version 7.11.20151209 for x86_64-apple-darwin): tcMonoExpr _ }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11184#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11184: panic tcMonoExpr _ with bad indentation in TH code -------------------------------------+------------------------------------- Reporter: TeroLaitinen | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Can you give a repro case that does not depend on Aeson? Thanks -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11184#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11184: panic tcMonoExpr _ with bad indentation in TH code -------------------------------------+------------------------------------- Reporter: TeroLaitinen | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by phadej): {{{ {-# LANGUAGE TemplateHaskell #-} $((\x -> case x of "foo" -> "bar" _ -> x)) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11184#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11184: panic tcMonoExpr _ with bad indentation in TH code -------------------------------------+------------------------------------- Reporter: TeroLaitinen | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mgsloan): Perhaps this is worth another bug report, but here's another case: {{{ {-# LANGUAGE TemplateHaskell #-} -- A realistic example, demonstrating how this can be baffling in real code. $(mapM (n -> [d| foo = n |]) [1]) -- Minimal example $((x -> x)) }}} causes {{{ ghc: panic! (the 'impossible' happened) (GHC version 7.10.3 for x86_64-unknown-linux): tcMonoExpr _ }}} Similarly, this is likely due to expressions and patterns sharing parsing. We just need to do the same checks that are applied to normal user code. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11184#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11184: panic tcMonoExpr _ with bad indentation in TH code -------------------------------------+------------------------------------- Reporter: TeroLaitinen | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.2 Resolution: | Keywords: | TemplateHaskell Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: => TemplateHaskell * component: Compiler => Template Haskell -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11184#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11184: panic tcMonoExpr _ with bad indentation in TH code -------------------------------------+------------------------------------- Reporter: TeroLaitinen | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.2 Resolution: | Keywords: | TemplateHaskell Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by erikd): The panic occurs for the `EWildPat` constructor and the comments for that constructor (and some others) say (in the file compiler/hsSyn/HsExpr.hs): {{{ -- These constructors only appear temporarily in the parser. -- The renamer translates them into the Right Thing. }}} so the problem isn't really that the `EWildPat` constructor isn't handled, but rather that an error should have been reported when the renamer failed to translate it into the Right Thing. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11184#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11184: panic tcMonoExpr _ with bad indentation in TH code -------------------------------------+------------------------------------- Reporter: TeroLaitinen | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Template Haskell | Version: 7.10.2 Resolution: duplicate | Keywords: | TemplateHaskell Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: #12584 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => duplicate * related: => #12584 * milestone: => 8.0.2 Comment: This was fixed by the solution for #12584. This fix has been applied to GHC 8.0.2 and HEAD. For reference, with GHC HEAD the reported error message for the original code is now: {{{ GHCi, version 8.1.20161023: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Main ( Bug.hs, interpreted ) Bug.hs:8:26: error: Pattern syntax in expression context: \ x -> case x of { "type_" -> "type" (...) } -> x }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11184#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC