Skip to content

Commit

Permalink
Merge branch 'master' into overlapping-tyfams
Browse files Browse the repository at this point in the history
  • Loading branch information
Richard Eisenberg committed May 28, 2013
2 parents 198b2b8 + 083397f commit 2858b49
Show file tree
Hide file tree
Showing 13 changed files with 52 additions and 9 deletions.
7 changes: 7 additions & 0 deletions 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 ())
1 change: 1 addition & 0 deletions tests/deriving/should_run/T7931.stderr
@@ -0,0 +1 @@
T7931: Derived Read on empty data type
1 change: 1 addition & 0 deletions tests/deriving/should_run/all.T
Expand Up @@ -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, [''])

3 changes: 2 additions & 1 deletion tests/ghci/scripts/T7627.stdout
Expand Up @@ -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)
Expand Down
8 changes: 8 additions & 0 deletions tests/ghci/scripts/T7939.hs
@@ -0,0 +1,8 @@
{-# LANGUAGE TypeFamilies, PolyKinds #-}

module T7939 where

class Foo a where
type Bar a


3 changes: 3 additions & 0 deletions tests/ghci/scripts/T7939.script
@@ -0,0 +1,3 @@
:l T7939
:i Bar
:k Bar
4 changes: 4 additions & 0 deletions 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
1 change: 1 addition & 0 deletions tests/ghci/scripts/all.T
Expand Up @@ -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'])

4 changes: 2 additions & 2 deletions tests/ghci/scripts/ghci025.stdout
Expand Up @@ -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
Expand All @@ -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
Expand Down
14 changes: 8 additions & 6 deletions 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
10 changes: 10 additions & 0 deletions 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


4 changes: 4 additions & 0 deletions tests/rename/should_fail/T7937.stderr
@@ -0,0 +1,4 @@

T7937.hs:8:13:
Not in scope: ‛***’
Perhaps you meant ‛**’ (imported from Prelude)
1 change: 1 addition & 0 deletions tests/rename/should_fail/all.T
Expand Up @@ -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, [''])

0 comments on commit 2858b49

Please sign in to comment.