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
Glasgow Haskell Compiler
GHC
Commits
280de0c1
Commit
280de0c1
authored
May 08, 2018
by
Ben Gamari
🐢
Browse files
Revert "Normalize the element type of ListPat, fix
#14547
"
This reverts commit
361d23a8
.
parent
37acca7e
Changes
3
Show whitespace changes
Inline
Side-by-side
compiler/deSugar/Check.hs
View file @
280de0c1
...
@@ -790,13 +790,10 @@ translatePat fam_insts pat = case pat of
...
@@ -790,13 +790,10 @@ translatePat fam_insts pat = case pat of
-- overloaded list
-- overloaded list
ListPat
(
ListPatTc
elem_ty
(
Just
(
pat_ty
,
_to_list
)))
lpats
ListPat
(
ListPatTc
elem_ty
(
Just
(
pat_ty
,
_to_list
)))
lpats
|
Just
e_ty
<-
splitListTyConApp_maybe
pat_ty
|
Just
e_ty
<-
splitListTyConApp_maybe
pat_ty
,
(
_
,
norm_e_ty
)
<-
normaliseType
fam_insts
Nominal
e_ty
-- e_ty can be a type family instance, like
-- `It (List a)`, but we prefer `a`, see Trac #14547
,
(
_
,
norm_elem_ty
)
<-
normaliseType
fam_insts
Nominal
elem_ty
,
(
_
,
norm_elem_ty
)
<-
normaliseType
fam_insts
Nominal
elem_ty
-- elem_ty is frequently something like
-- elem_ty is frequently something like
-- `Item [Int]`, but we prefer `Int`
-- `Item [Int]`, but we prefer `Int`
,
norm_elem_ty
`
eqType
`
norm_
e_ty
->
,
norm_elem_ty
`
eqType
`
e_ty
->
-- We have to ensure that the element types are exactly the same.
-- We have to ensure that the element types are exactly the same.
-- Otherwise, one may give an instance IsList [Int] (more specific than
-- Otherwise, one may give an instance IsList [Int] (more specific than
-- the default IsList [a]) with a different implementation for `toList'
-- the default IsList [a]) with a different implementation for `toList'
...
...
testsuite/tests/deSugar/should_compile/T14547.hs
deleted
100644 → 0
View file @
37acca7e
{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE TypeFamilies #-}
module
T14547
where
class
Foo
f
where
type
It
f
foo
::
[
It
f
]
->
f
data
List
a
=
Empty
|
a
:!
List
a
deriving
Show
instance
Foo
(
List
a
)
where
type
It
(
List
a
)
=
a
foo
[]
=
Empty
foo
(
x
:
xs
)
=
x
:!
foo
xs
testsuite/tests/deSugar/should_compile/all.T
View file @
280de0c1
...
@@ -100,7 +100,6 @@ test('T13290', normal, compile, [''])
...
@@ -100,7 +100,6 @@ test('T13290', normal, compile, [''])
test
('
T13257
',
normal
,
compile
,
[''])
test
('
T13257
',
normal
,
compile
,
[''])
test
('
T13870
',
normal
,
compile
,
[''])
test
('
T13870
',
normal
,
compile
,
[''])
test
('
T14135
',
normal
,
compile
,
[''])
test
('
T14135
',
normal
,
compile
,
[''])
test
('
T14547
',
normal
,
compile
,
['
-Wincomplete-patterns
'])
test
('
T14773a
',
normal
,
compile
,
['
-Wincomplete-patterns
'])
test
('
T14773a
',
normal
,
compile
,
['
-Wincomplete-patterns
'])
test
('
T14773b
',
normal
,
compile
,
['
-Wincomplete-patterns
'])
test
('
T14773b
',
normal
,
compile
,
['
-Wincomplete-patterns
'])
test
('
T14815
',
[]
,
run_command
,
['
$MAKE -s --no-print-directory T14815
'])
test
('
T14815
',
[]
,
run_command
,
['
$MAKE -s --no-print-directory T14815
'])
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