Skip to content
Snippets Groups Projects
Commit 827f8cea authored by Simon Peyton Jones's avatar Simon Peyton Jones
Browse files

Tests for Trac #1825

parent f9b1bfe1
No related branches found
No related tags found
No related merge requests found
......@@ -14,3 +14,4 @@ test('drv013', normal, compile, [''])
test('drv014', normal, compile, [''])
test('drv015', normal, compile, [''])
test('drv020', normal, compile, [''])
test('drv021', normal, compile, [''])
{-# OPTIONS_GHC -XDeriveDataTypeable -XStandaloneDeriving #-}
-- See Trac #1825
-- Test stand-alone deriving for Typeable
-- Horridly, one needs to define instance for Typeable1 etc
module ShouldCompile where
import Data.Typeable
data T1 a = T1 a
data T2 a b = T2 a b
deriving instance Typeable1 T1
deriving instance Typeable2 T2
......@@ -12,3 +12,4 @@ test('drvfail010', normal, compile_fail, [''])
test('drvfail011', normal, compile_fail, [''])
test('drvfail012', normal, compile_fail, [''])
test('drvfail013', normal, compile_fail, [''])
test('drvfail014', normal, compile_fail, [''])
{-# OPTIONS_GHC -XDeriveDataTypeable -XStandaloneDeriving #-}
-- See Trac #1825
module ShouldFail where
import Data.Typeable
data T1 a = T1 a deriving( Typeable1 )
data T2 a b = T2 a b
deriving instance (Typeable a, Typeable b) => Typeable (T2 a b)
-- c.f. drv021.hs
drvfail014.hs:8:0:
Use deriving( Typeable ) on a data type declaration
In the data type declaration for `T1'
drvfail014.hs:12:0:
Derived typeable instance must be of form (Typeable2 T2)
In the stand-alone deriving instance for
`(Typeable a, Typeable b) => Typeable (T2 a b)'
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment