[GHC] #11188: Confusing "parse error in pattern" for missing indentation.

#11188: Confusing "parse error in pattern" for missing indentation. -------------------------------------+------------------------------------- Reporter: andreas.abel | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.1 (Parser) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Other Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The following problem exists at least in ghc 7.4.2 through 7.10.1: {{{#!hs main = do putStrLn "Hello, lots of crap" $ do a <- return 3 -- The following line is mis-indented, the error is incomprehensible c <- do return 5 }}} Error: {{{ <file>:2:3: Parse error in pattern: putStrLn Possibly caused by a missing 'do'? }}} The hint about "missing do" exists from ghc 7.8, but is wrong in this case. Problematic about this bug is that the wrong indentation can be arbitrary many lines from where ghc reports the (totally incomprehensible) error. My original problem is to find the syntax error here: {{{#!hs -- | Type check a function clause. checkClause :: Type -> A.SpineClause -> TCM Clause checkClause t c@(A.Clause (A.SpineLHS i x aps withPats) rhs0 wh) = do unless (null withPats) $ do typeError $ UnexpectedWithPatterns withPats traceCall (CheckClause t c) $ do aps <- expandPatternSynonyms aps checkLeftHandSide (CheckPatternShadowing c) (Just x) aps t $ \ (LHSResult delta ps trhs perm) -> do -- Note that we might now be in irrelevant context, -- in case checkLeftHandSide walked over an irrelevant projection pattern. -- As we will be type-checking the @rhs@ in @delta@, but the final -- body should have bindings in the order of the pattern variables, -- we need to apply the permutation to the checked rhs @v@. let mkBody v = foldr (\ x t -> Bind $ Abs x t) b xs where b = Body $ applySubst (renamingR perm) v xs = [ stringToArgName $ "h" ++ show n | n <- [0..permRange perm - 1] ] -- introduce trailing implicits for checking the where decls TelV htel t0 <- telViewUpTo' (-1) (not . visible) $ unArg trhs (body, with) <- do let n = size htel addCtxTel htel $ checkWhere (size delta + n) wh $ -- for the body, we remove the implicits again escapeContext n $ handleRHS aps (unArgs trhs) rhs0 escapeContext (size delta) $ checkWithFunction with reportSDoc "tc.lhs.top" 10 $ escapeContext (size delta) $ vcat [ text "Clause before translation:" , nest 2 $ vcat [ text "delta =" <+> prettyTCM delta , text "perm =" <+> text (show perm) , text "ps =" <+> text (show ps) , text "body =" <+> text (show body) , text "body =" <+> prettyTCM body ] ] return $ Clause { clauseRange = getRange i , clauseTel = killRange delta , clausePerm = perm , namedClausePats = ps , clauseBody = body , clauseType = Just trhs } }}} {{{ src/full/Agda/TypeChecking/Rules/Def.hs:328:5: Parse error in pattern: checkLeftHandSide Possibly caused by a missing 'do'? }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11188 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11188: Confusing "parse error in pattern" for spurious indentation. -------------------------------------+------------------------------------- Reporter: andreas.abel | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.1 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11188#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11188: Confusing "parse error in pattern" for spurious indentation. -------------------------------------+------------------------------------- Reporter: andreas.abel | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.1 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * failure: Other => Incorrect warning at compile-time -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11188#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11188: Confusing "parse error in pattern" for spurious indentation. -------------------------------------+------------------------------------- Reporter: andreas.abel | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.1 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by thomie): The suggestion `Possibly caused by a missing 'do'` was added in #984. [ticket:984#comment:9 comment 9] in that ticket says: "Only time will tell whether this causes more confusion (in cases where the suggestion is wrong) than it resolves." -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11188#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11188: Confusing "parse error in pattern" for spurious indentation. -------------------------------------+------------------------------------- Reporter: andreas.abel | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.1 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4497 Wiki Page: | -------------------------------------+------------------------------------- Changes (by osa1): * differential: => Phab:D4497 Comment: I think the problem here is not that it's suggesting adding more `do`s (it's saying "possibly", meaning the reason may be something else), but it's showing only a small part of the large expression that the parser considers as a pattern. I submitted Phab:D4497 to improve this. Previously the error message was: {{{ Main.hs:2:3: error: Parse error in pattern: putStrLn Possibly caused by a missing 'do'? | 2 | putStrLn "" $ do | ^^^^^^^^^^^ }}} this is not good enough because it doesn't show the whole part that's considered as a pattern. With Phab:D4497: {{{ Main.hs:2:3: error: Parse error in pattern: putStrLn "" $ do a <- return 3 c Possibly caused by a missing 'do'? putStrLn "" $ do a <- return 3 c | 2 | putStrLn "" $ do | ^^^^^^^^^^^^^^^^... }}} It's now clear that left hand side of second `<-` now covers the first `<-` because the whole part is shown. If the error message is still not good enough perhaps we can split the parsers for expressions and patterns (rather than using expression parser for patterns and then doing a check to see whether it's a valid pattern). In that case I think we'd still get a parse error in expression parser while parsing `return 3 c <- do ...` which would raise a better error message I think. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11188#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11188: Confusing "parse error in pattern" for spurious indentation. -------------------------------------+------------------------------------- Reporter: andreas.abel | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.1 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #984 | Differential Rev(s): Phab:D4497 Wiki Page: | -------------------------------------+------------------------------------- Changes (by osa1): * related: => #984 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11188#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11188: Confusing "parse error in pattern" for spurious indentation.
-------------------------------------+-------------------------------------
Reporter: andreas.abel | Owner: (none)
Type: bug | Status: new
Priority: high | Milestone:
Component: Compiler | Version: 7.10.1
(Parser) |
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Incorrect | Unknown/Multiple
warning at compile-time | Test Case:
Blocked By: | Blocking:
Related Tickets: #984 | Differential Rev(s): Phab:D4497
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ömer Sinan Ağacan

#11188: Confusing "parse error in pattern" for spurious indentation. -------------------------------------+------------------------------------- Reporter: andreas.abel | Owner: (none) Type: bug | Status: merge Priority: high | Milestone: Component: Compiler | Version: 7.10.1 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #984 | Differential Rev(s): Phab:D4497 Wiki Page: | -------------------------------------+------------------------------------- Changes (by osa1): * status: new => merge Comment: We discussed this and thought this improvement should be enough for now. Please let us know if the error is still not good enough. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11188#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11188: Confusing "parse error in pattern" for spurious indentation. -------------------------------------+------------------------------------- Reporter: andreas.abel | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 (Parser) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #984 | Differential Rev(s): Phab:D4497 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * priority: high => normal * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-8.4`. Closing but do feel free to reopen if you can think of anything more we can do here. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11188#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11188: Confusing "parse error in pattern" for spurious indentation. -------------------------------------+------------------------------------- Reporter: andreas.abel | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.2 Component: Compiler | Version: 7.10.1 (Parser) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #984 | Differential Rev(s): Phab:D4497 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: => 8.4.2 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11188#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC