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

GHC ghc-devs at haskell.org
Wed Dec 9 19:56:36 UTC 2015


#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 at .
         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


More information about the ghc-tickets mailing list