Skip to content
Snippets Groups Projects
Commit df8e8ba2 authored by Vladislav Zavialov's avatar Vladislav Zavialov Committed by Marge Bot
Browse files

Location for tuple section pattern error (#19504)

This fixes a regression that led to loss of location information
in error messages about the use of tuple sections in patterns.
parent e9189745
No related branches found
No related tags found
No related merge requests found
......@@ -2670,7 +2670,9 @@ mkSumOrTuplePat l boxity (Tuple ps) = do
return $ L l (PatBuilderPat (TuplePat noExtField ps' boxity))
where
toTupPat :: Located (Maybe (Located (PatBuilder GhcPs))) -> PV (LPat GhcPs)
toTupPat (L l p) = case p of
-- Ignore the element location so that the error message refers to the
-- entire tuple. See #19504 (and the discussion) for details.
toTupPat (L _ p) = case p of
Nothing -> addFatalError $ PsError PsErrTupleSectionInPat [] l
Just p' -> checkLPat p'
......
module T19504 where
error_notLocated = (\ (0, ) -> (0, undefined))
T19504.hs:3:23: error: Tuple section in pattern context
......@@ -189,3 +189,4 @@ test('RecordDotSyntaxFail10', normal, compile_fail, [''])
test('RecordDotSyntaxFail11', normal, compile_fail, [''])
test('RecordDotSyntaxFail12', normal, compile_fail, [''])
test('RecordDotSyntaxFail13', normal, compile_fail, [''])
test('T19504', normal, compile_fail, [''])
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment