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
Alex D
GHC
Commits
1db5bb2f
Commit
1db5bb2f
authored
Jun 27, 2008
by
simonpj
Browse files
Add a test that apparently made the typechecker loop (around Feb 08)
parent
cbce68ba
Changes
3
Hide whitespace changes
Inline
Side-by-side
testsuite/tests/ghc-regress/typecheck/should_fail/all.T
View file @
1db5bb2f
...
...
@@ -189,6 +189,7 @@ test('tcfail197', if_compiler_lt('ghc', '6.9', skip), compile_fail, [''])
test
('
tcfail198
',
normal
,
compile_fail
,
[''])
test
('
tcfail199
',
normal
,
compile_fail
,
[''])
test
('
tcfail200
',
if_compiler_lt
('
ghc
',
'
6.9
',
skip
),
compile_fail
,
[''])
test
('
tcfail201
',
normal
,
compile_fail
,
[''])
test
('
T1899
',
normal
,
compile_fail
,
[''])
test
('
T2126
',
normal
,
compile_fail
,
[''])
testsuite/tests/ghc-regress/typecheck/should_fail/tcfail201.hs
0 → 100644
View file @
1db5bb2f
{-# OPTIONS_GHC -fglasgow-exts #-}
-- Claus reported by email that
-- GHCi, version 6.9.20080217 loops on this program
-- http://www.haskell.org/pipermail/cvs-ghc/2008-June/043173.html
-- So I'm adding it to the test suite so that we'll see it if it happens again
module
Foo
where
data
HsDoc
id
=
DocEmpty
|
DocParagraph
(
HsDoc
id
)
gfoldl'
::
(
forall
a
b
.
c
(
a
->
b
)
->
a
->
c
b
)
->
(
forall
g
.
g
->
c
g
)
->
a
->
c
a
gfoldl'
k
z
hsDoc
=
case
hsDoc
of
DocEmpty
->
z
DocEmpty
(
DocParagraph
hsDoc
)
->
z
DocParagraph
`
k
`
hsDoc
testsuite/tests/ghc-regress/typecheck/should_fail/tcfail201.stderr
0 → 100644
View file @
1db5bb2f
tcfail201.hs:17:5:
Couldn't match expected type `a' against inferred type `HsDoc id'
`a' is a rigid type variable bound by
the type signature for `gfoldl'' at tcfail201.hs:15:77
In the pattern: DocEmpty
In a case alternative: DocEmpty -> z DocEmpty
In the expression:
case hsDoc of
DocEmpty -> z DocEmpty
(DocParagraph hsDoc) -> z DocParagraph `k` hsDoc
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