Skip to content
Snippets Groups Projects
Commit 854f7314 authored by Gergő Érdi's avatar Gergő Érdi Committed by Austin Seipp
Browse files

Require PatternSynonyms language flag when encountering a use of pattern synonym

(#8961)

(cherry picked from commit 8f831ec5)
parent e08adf97
No related branches found
No related tags found
No related merge requests found
......@@ -813,14 +813,12 @@ tcPatSynPat penv (L con_span _) pat_syn pat_ty arg_pats thing_inside
; prov_dicts' <- newEvVars prov_theta'
{-
-- Using a pattern synonym requires the PatternSynonyms
-- language flag to keep consistent with #2905
; patsyns_on <- xoptM Opt_PatternSynonyms
; checkTc patsyns_on
(ptext (sLit "A pattern match on a pattern synonym requires PatternSynonyms"))
-- Trac #2905 decided that a *pattern-match* of a GADT
-- should require the GADT language flag.
-- Re TypeFamilies see also #7156
-}
; let skol_info = case pe_ctxt penv of
LamPat mc -> PatSkol (PatSynCon pat_syn) mc
LetPat {} -> UnkSkol -- Doesn't matter
......
......@@ -7,3 +7,4 @@ test('ex-view', normal, compile, [''])
test('ex-num', normal, compile, [''])
test('num', normal, compile, [''])
test('incomplete', normal, compile, [''])
test('export', normal, compile, [''])
{-# LANGUAGE PatternSynonyms #-}
module ShouldCompile (pattern Single) where
pattern Single x <- [x]
module ShouldFail where
import T8961a
single :: [a] -> Maybe a
single (Single x) = Just x
single _ = Nothing
[1 of 2] Compiling T8961a ( T8961a.hs, T8961a.o )
[2 of 2] Compiling ShouldFail ( T8961.hs, T8961.o )
T8961.hs:6:9:
A pattern match on a pattern synonym requires PatternSynonyms
In the pattern: Single x
In an equation for ‘single’: single (Single x) = Just x
{-# LANGUAGE PatternSynonyms #-}
module T8961a (pattern Single) where
pattern Single x <- [x]
......@@ -2,3 +2,4 @@
test('mono', normal, compile_fail, [''])
test('unidir', normal, compile_fail, [''])
test('local', normal, compile_fail, [''])
test('T8961', normal, multimod_compile_fail, ['T8961',''])
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