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
71900040
Commit
71900040
authored
Jun 29, 2007
by
chak@cse.unsw.edu.au.
Browse files
Type families: tests for overlap check of type families
parent
89f0cdd1
Changes
10
Hide whitespace changes
Inline
Side-by-side
testsuite/tests/ghc-regress/indexed-types/should_fail/Over.stderr
View file @
71900040
...
...
@@ -7,3 +7,8 @@ OverB.hs:7:14:
Conflicting family instance declarations:
data instance OverA.C [Int] [a] -- Defined at OverB.hs:7:14
data instance OverA.C [a] [Int] -- Defined at OverC.hs:7:14
OverB.hs:9:14:
Conflicting family instance declarations:
type instance OverA.D [Int] [a] -- Defined at OverB.hs:9:14
type instance OverA.D [a] [Int] -- Defined at OverC.hs:9:14
testsuite/tests/ghc-regress/indexed-types/should_fail/OverA.hs
View file @
71900040
{-# OPTIONS -ftype-families -fglasgow-exts #-}
module
OverA
(
C
)
module
OverA
(
C
,
D
)
where
data
family
C
a
b
::
*
type
family
D
a
b
::
*
\ No newline at end of file
testsuite/tests/ghc-regress/indexed-types/should_fail/OverB.hs
View file @
71900040
...
...
@@ -2,6 +2,8 @@
module
OverB
where
import
OverA
(
C
)
import
OverA
(
C
,
D
)
data
instance
C
[
Int
]
[
a
]
=
CListList2
type
instance
D
[
Int
]
[
a
]
=
Int
\ No newline at end of file
testsuite/tests/ghc-regress/indexed-types/should_fail/OverC.hs
View file @
71900040
...
...
@@ -2,6 +2,8 @@
module
OverC
where
import
OverA
(
C
)
import
OverA
(
C
,
D
)
data
instance
C
[
a
]
[
Int
]
=
C9ListList
type
instance
D
[
a
]
[
Int
]
=
Char
testsuite/tests/ghc-regress/indexed-types/should_fail/Simple11a.hs
View file @
71900040
...
...
@@ -6,3 +6,8 @@ data family C9 a b :: *
data
instance
C9
Int
Int
=
C9IntInt
-- must fail: conflicting
data
instance
C9
Int
Int
=
C9IntInt2
type
family
D9
a
b
::
*
type
instance
D9
Int
Int
=
Char
-- must fail: conflicting
type
instance
D9
Int
Int
=
Int
testsuite/tests/ghc-regress/indexed-types/should_fail/Simple11a.stderr
View file @
71900040
...
...
@@ -3,3 +3,8 @@ Simple11a.hs:6:14:
Conflicting family instance declarations:
data instance C9 Int Int -- Defined at Simple11a.hs:6:14-15
data instance C9 Int Int -- Defined at Simple11a.hs:8:14-15
Simple11a.hs:11:14:
Conflicting family instance declarations:
type instance D9 Int Int -- Defined at Simple11a.hs:11:14-15
type instance D9 Int Int -- Defined at Simple11a.hs:13:14-15
testsuite/tests/ghc-regress/indexed-types/should_fail/Simple11b.hs
View file @
71900040
...
...
@@ -7,3 +7,12 @@ data instance C9 Int Int = C9IntInt
data
instance
C9
[
a
]
Int
=
C9ListInt
-- must fail: conflicting
data
instance
C9
[
a
]
Int
=
C9ListInt2
type
family
D9
a
b
::
*
type
instance
D9
Int
Int
=
Int
type
instance
D9
[
a
]
Int
=
[
a
]
-- must fail: conflicting
type
instance
D9
[
a
]
Int
=
Maybe
a
type
instance
D9
Int
[
a
]
=
[
a
]
type
instance
D9
Int
[
b
]
=
[
b
]
-- must not conflict!
testsuite/tests/ghc-regress/indexed-types/should_fail/Simple11b.stderr
View file @
71900040
...
...
@@ -3,3 +3,8 @@ Simple11b.hs:7:14:
Conflicting family instance declarations:
data instance C9 [a] Int -- Defined at Simple11b.hs:7:14-15
data instance C9 [a] Int -- Defined at Simple11b.hs:9:14-15
Simple11b.hs:13:14:
Conflicting family instance declarations:
type instance D9 [a] Int -- Defined at Simple11b.hs:13:14-15
type instance D9 [a] Int -- Defined at Simple11b.hs:15:14-15
testsuite/tests/ghc-regress/indexed-types/should_fail/Simple11c.hs
View file @
71900040
...
...
@@ -7,3 +7,15 @@ data instance C9 Int Int = C9IntInt
data
instance
C9
[
a
]
Int
=
C9ListInt
-- must fail: conflicting
data
instance
C9
[
Int
]
Int
=
C9ListInt2
type
family
D9
a
b
::
*
type
instance
D9
Int
Int
=
Int
type
instance
D9
[
a
]
Int
=
[
a
]
-- must fail: conflicting
type
instance
D9
[
Int
]
Int
=
[
Bool
]
type
family
E9
a
b
::
*
type
instance
E9
Int
Int
=
Int
type
instance
E9
[
a
]
Int
=
[
a
]
type
instance
E9
[
Int
]
Int
=
[
Int
]
-- does *not* conflict!
type
instance
E9
b
Int
=
b
testsuite/tests/ghc-regress/indexed-types/should_fail/Simple11c.stderr
View file @
71900040
...
...
@@ -3,3 +3,8 @@ Simple11c.hs:7:14:
Conflicting family instance declarations:
data instance C9 [a] Int -- Defined at Simple11c.hs:7:14-15
data instance C9 [Int] Int -- Defined at Simple11c.hs:9:14-15
Simple11c.hs:13:14:
Conflicting family instance declarations:
type instance D9 [a] Int -- Defined at Simple11c.hs:13:14-15
type instance D9 [Int] Int -- Defined at Simple11c.hs:15:14-15
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