From 254605de0b64016e6b8abb202b2391e78f319ecd Mon Sep 17 00:00:00 2001 From: Simon Peyton Jones Date: Mon, 27 May 2013 17:32:07 +0100 Subject: [PATCH 1/4] Test Trac #7939 --- tests/ghci/scripts/T7939.hs | 8 ++++++++ tests/ghci/scripts/T7939.script | 3 +++ tests/ghci/scripts/T7939.stdout | 4 ++++ tests/ghci/scripts/all.T | 1 + 4 files changed, 16 insertions(+) create mode 100644 tests/ghci/scripts/T7939.hs create mode 100644 tests/ghci/scripts/T7939.script create mode 100644 tests/ghci/scripts/T7939.stdout diff --git a/tests/ghci/scripts/T7939.hs b/tests/ghci/scripts/T7939.hs new file mode 100644 index 000000000..ead42d91b --- /dev/null +++ b/tests/ghci/scripts/T7939.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE TypeFamilies, PolyKinds #-} + +module T7939 where + +class Foo a where + type Bar a + + diff --git a/tests/ghci/scripts/T7939.script b/tests/ghci/scripts/T7939.script new file mode 100644 index 000000000..03470e81a --- /dev/null +++ b/tests/ghci/scripts/T7939.script @@ -0,0 +1,3 @@ +:l T7939 +:i Bar +:k Bar diff --git a/tests/ghci/scripts/T7939.stdout b/tests/ghci/scripts/T7939.stdout new file mode 100644 index 000000000..c62de9b5f --- /dev/null +++ b/tests/ghci/scripts/T7939.stdout @@ -0,0 +1,4 @@ +class Foo (k :: BOX) (a :: k) where + type family Bar (k :: BOX) (k :: BOX) (a :: k) :: k + -- Defined at T7939.hs:6:9 +Bar :: k1 -> k diff --git a/tests/ghci/scripts/all.T b/tests/ghci/scripts/all.T index afe46a13c..cf8c82b7e 100755 --- a/tests/ghci/scripts/all.T +++ b/tests/ghci/scripts/all.T @@ -149,4 +149,5 @@ test('T7586', normal, ghci_script, ['T7586.script']) test('T4175', normal, ghci_script, ['T4175.script']) test('T7872', normal, ghci_script, ['T7872.script']) test('T7873', normal, ghci_script, ['T7873.script']) +test('T7939', normal, ghci_script, ['T7939.script']) From 1ed0be84d39a488d36bedffcc1a91be1bb39d52a Mon Sep 17 00:00:00 2001 From: Simon Peyton Jones Date: Mon, 27 May 2013 17:32:45 +0100 Subject: [PATCH 2/4] Test Trac #7931 --- tests/deriving/should_run/T7931.hs | 7 +++++++ tests/deriving/should_run/T7931.stderr | 1 + tests/deriving/should_run/all.T | 1 + 3 files changed, 9 insertions(+) create mode 100644 tests/deriving/should_run/T7931.hs create mode 100644 tests/deriving/should_run/T7931.stderr diff --git a/tests/deriving/should_run/T7931.hs b/tests/deriving/should_run/T7931.hs new file mode 100644 index 000000000..052b68205 --- /dev/null +++ b/tests/deriving/should_run/T7931.hs @@ -0,0 +1,7 @@ +{-# LANGUAGE StandaloneDeriving #-} +module Main where + +data A +deriving instance Read A + +main = seq (read "" :: A) (return ()) diff --git a/tests/deriving/should_run/T7931.stderr b/tests/deriving/should_run/T7931.stderr new file mode 100644 index 000000000..74be9c975 --- /dev/null +++ b/tests/deriving/should_run/T7931.stderr @@ -0,0 +1 @@ +T7931: Derived Read on empty data type diff --git a/tests/deriving/should_run/all.T b/tests/deriving/should_run/all.T index af4bd720c..cfef4c3cb 100644 --- a/tests/deriving/should_run/all.T +++ b/tests/deriving/should_run/all.T @@ -34,4 +34,5 @@ test('T4528a', normal, compile_and_run, ['']) test('T5041', normal, compile_and_run, ['']) test('T5628', exit_code(1), compile_and_run, ['']) test('T5712', normal, compile_and_run, ['']) +test('T7931', exit_code(1), compile_and_run, ['']) From 3152092d9149388fe580dc042c6acac470d60dd7 Mon Sep 17 00:00:00 2001 From: Simon Peyton Jones Date: Mon, 27 May 2013 17:33:13 +0100 Subject: [PATCH 3/4] Explicit kinds in :info command ===> testsuite wibbles --- tests/ghci/scripts/T7627.stdout | 3 ++- tests/ghci/scripts/ghci025.stdout | 4 ++-- tests/ghci/scripts/ghci027.stdout | 14 ++++++++------ 3 files changed, 12 insertions(+), 9 deletions(-) diff --git a/tests/ghci/scripts/T7627.stdout b/tests/ghci/scripts/T7627.stdout index a23781a9d..351b9abd6 100644 --- a/tests/ghci/scripts/T7627.stdout +++ b/tests/ghci/scripts/T7627.stdout @@ -18,7 +18,8 @@ instance Functor ((,) a) -- Defined in ‛GHC.Base’ instance (Ord a, Ord b) => Ord (a, b) -- Defined in ‛GHC.Classes’ instance (Read a, Read b) => Read (a, b) -- Defined in ‛GHC.Read’ instance (Show a, Show b) => Show (a, b) -- Defined in ‛GHC.Show’ -data (#,#) a b = (#,#) a b -- Defined in ‛GHC.Prim’ +data (#,#) (a :: OpenKind) (b :: OpenKind) = (#,#) a b + -- Defined in ‛GHC.Prim’ (,) :: a -> b -> (a, b) (#,#) :: a -> b -> (# a, b #) ( , ) :: a -> b -> (a, b) diff --git a/tests/ghci/scripts/ghci025.stdout b/tests/ghci/scripts/ghci025.stdout index 3650de21c..9308dd3f3 100644 --- a/tests/ghci/scripts/ghci025.stdout +++ b/tests/ghci/scripts/ghci025.stdout @@ -14,7 +14,7 @@ c2 :: (C a b, N b, S b) => a -> b c3 :: C a b => forall a1. a1 -> b c4 :: C a b => forall a1. a1 -> b -- imported via Control.Monad -class Monad m => MonadPlus m where +class Monad m => MonadPlus (m :: * -> *) where mzero :: m a mplus :: m a -> m a -> m a mplus :: MonadPlus m => forall a. m a -> m a -> m a @@ -25,7 +25,7 @@ mzero :: MonadPlus m => forall a. m a fail :: Monad m => forall a. GHC.Base.String -> m a return :: Monad m => forall a. a -> m a -- imported via Control.Monad, Prelude, T -class Monad m where +class Monad (m :: * -> *) where (>>=) :: m a -> (a -> m b) -> m b (>>) :: m a -> m b -> m b return :: a -> m a diff --git a/tests/ghci/scripts/ghci027.stdout b/tests/ghci/scripts/ghci027.stdout index 2f627b46e..0d722c9d8 100644 --- a/tests/ghci/scripts/ghci027.stdout +++ b/tests/ghci/scripts/ghci027.stdout @@ -1,6 +1,8 @@ -class GHC.Base.Monad m => Control.Monad.MonadPlus m where - ... - mplus :: m a -> m a -> m a -class GHC.Base.Monad m => Control.Monad.MonadPlus m where - ... - Control.Monad.mplus :: m a -> m a -> m a +class GHC.Base.Monad m => + Control.Monad.MonadPlus (m :: * -> *) where + ... + mplus :: m a -> m a -> m a +class GHC.Base.Monad m => + Control.Monad.MonadPlus (m :: * -> *) where + ... + Control.Monad.mplus :: m a -> m a -> m a From 083397ff21ec9e254b0a7e36550a8a4ba50a5313 Mon Sep 17 00:00:00 2001 From: Simon Peyton Jones Date: Tue, 28 May 2013 09:20:12 +0100 Subject: [PATCH 4/4] Test Trac #7937 --- tests/rename/should_fail/T7937.hs | 10 ++++++++++ tests/rename/should_fail/T7937.stderr | 4 ++++ tests/rename/should_fail/all.T | 1 + 3 files changed, 15 insertions(+) create mode 100644 tests/rename/should_fail/T7937.hs create mode 100644 tests/rename/should_fail/T7937.stderr diff --git a/tests/rename/should_fail/T7937.hs b/tests/rename/should_fail/T7937.hs new file mode 100644 index 000000000..f47a31380 --- /dev/null +++ b/tests/rename/should_fail/T7937.hs @@ -0,0 +1,10 @@ +module T7937 where + +-- Without this operator definition, a precedence parsing error is reported. +-- Perhaps the default precedence is being assumed for the unknown operator? +-- That seems wrong, since there's no way to know what the precedence will be when +-- the operator is defined as the programmer intended. + +foo = 3 > 4 *** 5 == 6 + + diff --git a/tests/rename/should_fail/T7937.stderr b/tests/rename/should_fail/T7937.stderr new file mode 100644 index 000000000..09eb845cb --- /dev/null +++ b/tests/rename/should_fail/T7937.stderr @@ -0,0 +1,4 @@ + +T7937.hs:8:13: + Not in scope: ‛***’ + Perhaps you meant ‛**’ (imported from Prelude) diff --git a/tests/rename/should_fail/all.T b/tests/rename/should_fail/all.T index c1fbfac98..c94b39300 100644 --- a/tests/rename/should_fail/all.T +++ b/tests/rename/should_fail/all.T @@ -108,3 +108,4 @@ test('T7338', normal, compile_fail, ['']) test('T7338a', normal, compile_fail, ['']) test('T7454', normal, compile, ['']) test('T7906', normal, compile_fail, ['']) +test('T7937', normal, compile_fail, [''])