Skip to content
GitLab
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
d8baa233
Commit
d8baa233
authored
Jul 01, 2008
by
simonpj
Browse files
Update output
parent
95e199e4
Changes
38
Hide whitespace changes
Inline
Side-by-side
testsuite/tests/ghc-regress/deriving/should_fail/T2394.hs
0 → 100644
View file @
d8baa233
{-# OPTIONS_GHC -XDeriveDataTypeable -XStandaloneDeriving #-}
-- Test Trac #2394
module
Foo
where
import
Data.Generics
(
Data
)
deriving
instance
(
Data
a
,
Data
b
)
=>
Data
(
a
->
b
)
testsuite/tests/ghc-regress/deriving/should_fail/T2394.stderr
0 → 100644
View file @
d8baa233
T2394.hs:9:0:
Can't make a derived instance of `Data (a -> b)'
(The last argument of the instance must be a data or newtype application)
In the stand-alone deriving instance for
`(Data a, Data b) => Data (a -> b)'
testsuite/tests/ghc-regress/deriving/should_fail/all.T
View file @
d8baa233
...
...
@@ -14,3 +14,4 @@ test('drvfail012', normal, compile_fail, [''])
test
('
drvfail013
',
normal
,
compile_fail
,
[''])
test
('
drvfail014
',
normal
,
compile_fail
,
[''])
test
('
drvfail015
',
normal
,
compile_fail
,
[''])
test
('
T2394
',
normal
,
compile_fail
,
[''])
testsuite/tests/ghc-regress/deriving/should_fail/drvfail001.stderr
View file @
d8baa233
drvfail001.hs:1
5:0
:
drvfail001.hs:1
6:18
:
No instance for (Show (f (f a)))
arising from the 'deriving' clause of a data type declaration
at drvfail001.hs:
(15,0)-(16,
21
)
at drvfail001.hs:
16:18-
21
Possible fix: add an instance declaration for (Show (f (f a)))
When deriving the instance for (Show (SM f a))
testsuite/tests/ghc-regress/deriving/should_fail/drvfail003.stderr
View file @
d8baa233
drvfail003.hs:1
3:0
:
drvfail003.hs:1
6:55
:
No instance for (Show (v (v a)))
arising from the 'deriving' clause of a data type declaration
at drvfail003.hs:
(13,0)-(16,
58
)
at drvfail003.hs:
16:55-
58
Possible fix: add an instance declaration for (Show (v (v a)))
When deriving the instance for (Show (Square_ v w a))
testsuite/tests/ghc-regress/deriving/should_fail/drvfail004.stderr
View file @
d8baa233
drvfail004.hs:
5:0
:
drvfail004.hs:
8:11
:
No instance for (Eq (Foo a b))
arising from the 'deriving' clause of a data type declaration
at drvfail004.hs:
(5,0)-(8,
13
)
at drvfail004.hs:
8:11-
13
Possible fix: add an instance declaration for (Eq (Foo a b))
When deriving the instance for (Ord (Foo a b))
testsuite/tests/ghc-regress/deriving/should_fail/drvfail005.stderr
View file @
d8baa233
drvfail005.hs:
3:0
:
drvfail005.hs:
4:12
:
Can't make a derived instance of `Show a (Test a)'
(`Show a' is not a class)
In the data type declaration for `Test'
testsuite/tests/ghc-regress/deriving/should_fail/drvfail007.stderr
View file @
d8baa233
drvfail007.hs:4:
0
:
drvfail007.hs:4:
37
:
No instance for (Eq (Int -> Int))
arising from the 'deriving' clause of a data type declaration
at drvfail007.hs:4:
0
-38
at drvfail007.hs:4:
37
-38
Possible fix: add an instance declaration for (Eq (Int -> Int))
When deriving the instance for (Eq Foo)
testsuite/tests/ghc-regress/deriving/should_fail/drvfail009.stderr
View file @
d8baa233
drvfail009.hs:10:0:
drvfail009.hs:10:
3
0:
Can't make a derived instance of `C T1'
(even with cunning newtype deriving:
`C' does not have arity 1)
In the newtype declaration for `T1'
drvfail009.hs:13:0:
drvfail009.hs:13:
3
0:
Can't make a derived instance of `Monad T2'
(even with cunning newtype deriving:
the type constructor has wrong kind)
In the newtype declaration for `T2'
drvfail009.hs:16:
0
:
drvfail009.hs:16:
32
:
Can't make a derived instance of `Monad T3'
(even with cunning newtype deriving:
the representation type has wrong kind)
In the newtype declaration for `T3'
drvfail009.hs:19:
0
:
drvfail009.hs:19:
41
:
Can't make a derived instance of `Monad T4'
(even with cunning newtype deriving:
the eta-reduction property does not hold)
...
...
testsuite/tests/ghc-regress/deriving/should_fail/drvfail010.stderr
View file @
d8baa233
drvfail010.hs:6:
0
:
drvfail010.hs:6:
41
:
Can't make a derived instance of `Typeable (A a b c d e f g h i j)'
(`A' has too many arguments)
In the data type declaration for `A'
drvfail010.hs:9:
0
:
drvfail010.hs:9:
31
:
Can't make a derived instance of `Typeable (B a b)'
(`B' has arguments of kind other than `*')
In the data type declaration for `B'
testsuite/tests/ghc-regress/deriving/should_fail/drvfail011.stderr
View file @
d8baa233
drvfail011.hs:
5:5
:
drvfail011.hs:
8:0
:
Could not deduce (Eq a) from the context (Eq (T a))
arising from a use of `==' at drvfail011.hs:
5:
5
arising from a use of `==' at drvfail011.hs:
8:0-2
5
Possible fix:
add (Eq a) to the context of the type signature for `=='
In the expression: ((a1 == b1))
...
...
testsuite/tests/ghc-regress/deriving/should_fail/drvfail012.stderr
View file @
d8baa233
drvfail012.hs:5:
0
:
drvfail012.hs:5:
32
:
No instance for (Eq (Ego a))
arising from the 'deriving' clause of a data type declaration
at drvfail012.hs:5:
0
-3
5
at drvfail012.hs:5:
32
-3
4
Possible fix: add an instance declaration for (Eq (Ego a))
When deriving the instance for (Ord (Ego a))
testsuite/tests/ghc-regress/deriving/should_fail/drvfail013.stderr
View file @
d8baa233
drvfail013.hs:4:
0
:
drvfail013.hs:4:
69
:
No instance for (Eq (m (Maybe a)))
arising from the 'deriving' clause of a data type declaration
at drvfail013.hs:4:
0
-70
at drvfail013.hs:4:
69
-70
Possible fix: add an instance declaration for (Eq (m (Maybe a)))
When deriving the instance for (Eq (MaybeT m a))
drvfail013.hs:6:
0
:
drvfail013.hs:6:
69
:
No instance for (Eq (m (Maybe a)))
arising from the 'deriving' clause of a data type declaration
at drvfail013.hs:6:
0
-70
at drvfail013.hs:6:
69
-70
Possible fix: add an instance declaration for (Eq (m (Maybe a)))
When deriving the instance for (Eq (MaybeT' m a))
testsuite/tests/ghc-regress/deriving/should_fail/drvfail014.stderr
View file @
d8baa233
drvfail014.hs:8:
0
:
drvfail014.hs:8:
27
:
Use deriving( Typeable ) on a data type declaration
In the data type declaration for `T1'
...
...
testsuite/tests/ghc-regress/indexed-types/should_compile/Simple2.stderr
View file @
d8baa233
Simple2.hs:21:0:
Warning: No explicit method nor default method for `foo3n'
In the instance declaration for `C3 Char'
Simple2.hs:21:0:
Warning: No explicit method nor default method for `bar3n'
In the instance declaration for `C3 Char'
Simple2.hs:21:0:
Warning: No explicit AT declaration for `S3n'
In the instance declaration for `C3 Char'
In the instance declaration for `C3 Char'
Simple2.hs:2
9:0
:
Simple2.hs:2
1:9
:
Warning: No explicit method nor default method for `foo3n'
In the instance declaration for `C3
Bool
'
In the instance declaration for `C3
Char
'
Simple2.hs:2
9:0
:
Simple2.hs:2
1:9
:
Warning: No explicit method nor default method for `bar3n'
In the instance declaration for `C3
Bool
'
In the instance declaration for `C3
Char
'
Simple2.hs:29:0:
Warning: No explicit AT declaration for `S3n'
In the instance declaration for `C3 Bool'
In the instance declaration for `C3 Bool'
Simple2.hs:
3
9:
0
:
Simple2.hs:
2
9:
9
:
Warning: No explicit method nor default method for `foo3n'
In the instance declaration for `C3
Float
'
In the instance declaration for `C3
Bool
'
Simple2.hs:
3
9:
0
:
Simple2.hs:
2
9:
9
:
Warning: No explicit method nor default method for `bar3n'
In the instance declaration for `C3
Float
'
In the instance declaration for `C3
Bool
'
Simple2.hs:39:0:
Warning: No explicit AT declaration for `S3'
In the instance declaration for `C3 Float'
In the instance declaration for `C3 Float'
Simple2.hs:39:0:
Warning: No explicit AT declaration for `S3n'
In the instance declaration for `C3 Float'
In the instance declaration for `C3 Float'
Simple2.hs:39:9:
Warning: No explicit method nor default method for `foo3n'
In the instance declaration for `C3 Float'
Simple2.hs:39:9:
Warning: No explicit method nor default method for `bar3n'
In the instance declaration for `C3 Float'
testsuite/tests/ghc-regress/module/mod46.stderr
View file @
d8baa233
mod46.hs:4:
0
:
mod46.hs:4:
9
:
No instance for (Eq T)
arising from the superclasses of an instance declaration at mod46.hs:4:0
arising from the superclasses of an instance declaration
at mod46.hs:4:9-13
Possible fix: add an instance declaration for (Eq T)
In the instance declaration for `Ord T'
testsuite/tests/ghc-regress/module/mod47.stderr
View file @
d8baa233
mod47.hs:6:
0
:
mod47.hs:6:
9
:
Could not deduce (Num a) from the context (Eq a, Enum a)
arising from the superclasses of an instance declaration
at mod47.hs:6:
0
at mod47.hs:6:
9-33
Possible fix:
add (Num a) to the context of the instance declaration
In the instance declaration for `Bar [a]'
testsuite/tests/ghc-regress/module/mod51.stderr
View file @
d8baa233
mod51.hs:3:
5
:
mod51.hs:3:
24
:
Duplicate instance declarations:
instance Eq T -- Defined at mod51.hs:3:5
instance Eq T -- Defined at mod51.hs:3:
5
instance Eq T -- Defined at mod51.hs:3:
24-2
5
instance Eq T -- Defined at mod51.hs:3:
21-22
testsuite/tests/ghc-regress/module/mod52.stderr
View file @
d8baa233
mod52.hs:3:
5
:
mod52.hs:3:
21
:
Duplicate instance declarations:
instance Eq T -- Defined at mod52.hs:3:
5
instance Eq T -- Defined at mod52.hs:4:
0
-12
instance Eq T -- Defined at mod52.hs:3:
21-22
instance Eq T -- Defined at mod52.hs:4:
9
-12
testsuite/tests/ghc-regress/module/mod53.stderr
View file @
d8baa233
mod53.hs:4:
0
:
mod53.hs:4:
21
:
Can't make a derived instance of `C T'
(`C' is not a derivable class)
In the data type declaration for `T'
Prev
1
2
Next
Write
Preview
Supports
Markdown
0%
Try again
or
attach a new 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