Skip to content
GitLab
Menu
Projects
Groups
Snippets
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Menu
Open sidebar
Shayne Fletcher
Glasgow Haskell Compiler
Commits
8f831ec5
Commit
8f831ec5
authored
Apr 06, 2014
by
Gergő Érdi
Browse files
Require PatternSynonyms language flag when encountering a use of pattern synonym
(#8961)
parent
f7723444
Changes
7
Hide whitespace changes
Inline
Side-by-side
compiler/typecheck/TcPat.lhs
View file @
8f831ec5
...
...
@@ -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
...
...
testsuite/tests/patsyn/should_compile/all.T
View file @
8f831ec5
...
...
@@ -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
,
[''])
testsuite/tests/patsyn/should_compile/export.hs
0 → 100644
View file @
8f831ec5
{-# LANGUAGE PatternSynonyms #-}
module
ShouldCompile
(
pattern
Single
)
where
pattern
Single
x
<-
[
x
]
testsuite/tests/patsyn/should_fail/T8961.hs
0 → 100644
View file @
8f831ec5
module
ShouldFail
where
import
T8961a
single
::
[
a
]
->
Maybe
a
single
(
Single
x
)
=
Just
x
single
_
=
Nothing
testsuite/tests/patsyn/should_fail/T8961.stderr
0 → 100644
View file @
8f831ec5
[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
testsuite/tests/patsyn/should_fail/T8961a.hs
0 → 100644
View file @
8f831ec5
{-# LANGUAGE PatternSynonyms #-}
module
T8961a
(
pattern
Single
)
where
pattern
Single
x
<-
[
x
]
testsuite/tests/patsyn/should_fail/all.T
View file @
8f831ec5
...
...
@@ -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
',''])
Write
Preview
Supports
Markdown
0%
Try again
or
attach a new file
.
Attach a file
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Cancel
Please
register
or
sign in
to comment