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
3dabbed3
Commit
3dabbed3
authored
Jun 14, 1999
by
simonpj
Browse files
[project @ 1999-06-14 09:29:01 by simonpj]
Accept some test changes; add tcfail082, read021
parent
1a32582e
Changes
27
Hide whitespace changes
Inline
Side-by-side
ghc/tests/ccall/should_fail/cc004.stderr
View file @
3dabbed3
cc004.hs:2:
Cannot generalise these overloadings (in a _ccall_):
`CReturnable b' arising from the result of the _ccall_ to `f' at cc004.hs:
15
`CReturnable b' arising from the result of the _ccall_ to `f' at cc004.hs:
8
cc004.hs:2:
Cannot generalise these overloadings (in a _ccall_):
`CReturnable b' arising from the result of the _ccall_ to `f' at cc004.hs:
8
`CReturnable b' arising from the result of the _ccall_ to `f' at cc004.hs:
15
Compilation had errors
ghc/tests/deSugar/should_compile/ds045.hs
0 → 100644
View file @
3dabbed3
!!
N
-
plus
-
K
pattern
in
binding
-- From: Andreas Marth
-- Sent: Monday, June 07, 1999 5:02 PM
-- To: glasgow-haskell-bugs@majordomo.haskell.org
-- Subject: compiler-bug
module
Test
where
erroR
::
Int
erroR
=
n
where
(
n
+
1
,
_
)
=
(
5
,
2
)
-- Produced a -dcore-lint error in the desugarer output
-- (Was a missing case in DsHsSyn.collectTypedPatBinders)
ghc/tests/reader/should_compile/read014.stderr
View file @
3dabbed3
...
...
@@ -5,22 +5,22 @@ read014.hs:4: Warning: Defined but not used: x
read014.hs:8: Warning: Defined but not used: x
read014.hs:
8
:
Warning: No explicit method nor default method for `
fromInteger
'
read014.hs:
6
:
Warning: No explicit method nor default method for `
+
'
in an instance declaration for `Num'
read014.hs:
8
:
Warning: No explicit method nor default method for `
signum
'
read014.hs:
6
:
Warning: No explicit method nor default method for `
*
'
in an instance declaration for `Num'
read014.hs:
8
:
read014.hs:
6
:
Warning: No explicit method nor default method for `abs'
in an instance declaration for `Num'
read014.hs:
8
:
Warning: No explicit method nor default method for `
*
'
read014.hs:
6
:
Warning: No explicit method nor default method for `
signum
'
in an instance declaration for `Num'
read014.hs:
8
:
Warning: No explicit method nor default method for `
+
'
read014.hs:
6
:
Warning: No explicit method nor default method for `
fromInteger
'
in an instance declaration for `Num'
ghc/tests/reader/should_compile/read021.hs
0 → 100644
View file @
3dabbed3
-- !!! Empty export list
module
Reader
()
where
instance
Show
(
a
->
b
)
where
show
f
=
"<<function>>"
ghc/tests/reader/should_fail/read004.stderr
View file @
3dabbed3
read004.hs:19:1: Illegal character: `.' in a string gap
read004.hs:19:1: on input: "."
read004.hs:14: error in character literal
Compilation had errors
ghc/tests/rename/should_compile/Rn016.hi
View file @
3dabbed3
...
...
@@ -5,5 +5,5 @@ instance {K PrelBase.Bool} = _f2;
instance __forall [a] => {K [a]} = _f3;
1 _f1 :: {K PrelBase.Int} ;
1 _f2 :: {K PrelBase.Bool} ;
1 _f3 :: __forall [a] => {K
PrelList.
[a]} ;
1 _f3 :: __forall [a] => {K [a]} ;
1 class K a :: (* -> *) where { op1 :: a -> a ; op2 :: a -> a } ;
ghc/tests/rename/should_fail/rnfail004.stderr
View file @
3dabbed3
rnfail004.hs:
6
:
rnfail004.hs:
7
:
Conflicting definitions for `a'
in a binding group
rnfail004.hs:
7
:
rnfail004.hs:
8
:
Conflicting definitions for `b'
in a binding group
...
...
ghc/tests/rename/should_fail/rnfail012.stderr
View file @
3dabbed3
rnfail012.hs:2:
Multiple declarations of `A'
defined at rnfail012.hs:
3
defined at rnfail012.hs:
9
defined at rnfail012.hs:
2
defined at rnfail012.hs:
8
Compilation had errors
ghc/tests/rename/should_fail/rnfail013.stderr
View file @
3dabbed3
rnfail013.hs:3:
Multiple declarations of `MkT'
defined at rnfail013.hs:5
defined at rnfail013.hs:7
defined at rnfail013.hs:9
Compilation had errors
ghc/tests/rename/should_fail/rnfail014.stderr
View file @
3dabbed3
rnfail014.hs:
9
:
rnfail014.hs:
8
:
None of the type variable(s) in the constraint `Eq a'
appears in the type `Eq Bool'
In the type signature for an instance decl
...
...
ghc/tests/rename/should_fail/rnfail015.stderr
View file @
3dabbed3
rnfail015.hs:
9
:
rnfail015.hs:
8
:
Conflicting definitions for `TokLiteral'
in the data type declaration for `Token'
...
...
ghc/tests/typecheck/should_fail/Data82.hs
0 → 100644
View file @
3dabbed3
module
Data82
where
data
FooData
=
FooData
ghc/tests/typecheck/should_fail/Digraph.stderr
View file @
3dabbed3
...
...
@@ -14,21 +14,21 @@ Digraph.hs:19:
([], [])
(snd (dfs (new_range es) ([], []) vs)))
where
span_tree r (vs, ns) [] = (vs, ns)
span_tree r (vs, ns) (x : xs)
| x `elem` vs = span_tree r (vs, ns) xs
| otherwise = span_tree r (vs', (x : ns') : ns) xs
where
(vs', ns') = dfs r (x : vs, []) (r x)
swap (x, y) = (y, x)
reversed_edges :: forall v. (Eq v) => [Edge v]
reversed_edges = map swap es
new_range [] w = []
new_range ((x, y) : xys) w
= if x == w then
(y : (new_range xys w))
else
(new_range xys w)
swap (x, y) = (y, x)
reversed_edges :: forall v. (Eq v) => [Edge v]
reversed_edges = map swap es
span_tree r (vs, ns) [] = (vs, ns)
span_tree r (vs, ns) (x : xs)
| x `elem` vs = span_tree r (vs, ns) xs
| otherwise = span_tree r (vs', (x : ns') : ns) xs
where
(vs', ns') = dfs r (x : vs, []) (r x)
Compilation had errors
ghc/tests/typecheck/should_fail/Inst82_1.hs
0 → 100644
View file @
3dabbed3
module
Inst82_1
where
import
Data82
instance
Read
FooData
where
readsPrec
_
_
=
[(
FooData
,
""
)]
ghc/tests/typecheck/should_fail/Inst82_2.hs
0 → 100644
View file @
3dabbed3
module
Inst82_2
where
import
Data82
instance
Read
FooData
where
readsPrec
_
_
=
[(
FooData
,
""
)]
ghc/tests/typecheck/should_fail/Makefile
View file @
3dabbed3
...
...
@@ -2,12 +2,22 @@ TOP = ../..
include
$(TOP)/mk/boilerplate.mk
include
$(TOP)/mk/should_fail.mk
SRC_HC_OPTS
+=
-noC
HS_SRCS
=
$(
wildcard
*
.hs
)
# The -noC messes up the Data82 compilation
# SRC_HC_OPTS += -noC
tcfail045_HC_OPTS
=
-fglasgow-exts
tcfail068_HC_OPTS
=
-fglasgow-exts
tcfail080_HC_OPTS
=
-fglasgow-exts
Inst82_1.o
:
Inst82_1.hs Data82.hi
$(HC)
$(HC_OPTS)
-c
$<
-o
$@
Inst82_2.o
:
Inst82_2.hs Data82.hi
$(HC)
$(HC_OPTS)
-c
$<
-o
$@
Data82.o
:
Data82.hs
$(HC)
$(HC_OPTS)
-c
$<
-o
$@
# mkdependHS doesn't understand OPTIONS pragmas...
SRC_MKDEPENDHS_OPTS
+=
-fglasgow-exts
...
...
ghc/tests/typecheck/should_fail/tcfail001.stderr
View file @
3dabbed3
tcfail001.hs:
9
:
tcfail001.hs:
8
:
Warning: Duplicate class assertion `A a' in the context:
(A a, A a) => ...
...
...
ghc/tests/typecheck/should_fail/tcfail017.stderr
View file @
3dabbed3
tcfail017.hs:1
1
:
tcfail017.hs:1
0
:
Could not deduce `C [a]'
(arising from an instance declaration at tcfail017.hs:1
1
)
(arising from an instance declaration at tcfail017.hs:1
0
)
from the context: (B a)
Probable cause: missing `C [a]' in instance declaration context
or missing instance declaration for `C [a]'
...
...
ghc/tests/typecheck/should_fail/tcfail019.stderr
View file @
3dabbed3
tcfail019.hs:1
9
:
tcfail019.hs:1
8
:
Could not deduce `C [a]'
(arising from an instance declaration at tcfail019.hs:1
9
)
(arising from an instance declaration at tcfail019.hs:1
8
)
from the context: ()
Probable cause: missing `C [a]' in instance declaration context
or missing instance declaration for `C [a]'
When checking the superclasses of an instance declaration
tcfail019.hs:1
9
:
tcfail019.hs:1
8
:
Could not deduce `B [a]'
(arising from an instance declaration at tcfail019.hs:1
9
)
(arising from an instance declaration at tcfail019.hs:1
8
)
from the context: ()
Probable cause: missing `B [a]' in instance declaration context
or missing instance declaration for `B [a]'
...
...
ghc/tests/typecheck/should_fail/tcfail020.stderr
View file @
3dabbed3
tcfail020.hs:1
1
:
tcfail020.hs:1
0
:
Could not deduce `A [a]'
(arising from an instance declaration at tcfail020.hs:1
1
)
(arising from an instance declaration at tcfail020.hs:1
0
)
from the context: (A a)
Probable cause: missing `A [a]' in instance declaration context
or missing instance declaration for `A [a]'
...
...
Prev
1
2
Next
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