Repository : ssh://darcs.haskell.org//srv/darcs/testsuite On branch : master
http://hackage.haskell.org/trac/ghc/changeset/8613162d8765e9983b278c81baeb5f92d371dc38 >--------------------------------------------------------------- commit 8613162d8765e9983b278c81baeb5f92d371dc38 Author: Simon Peyton Jones <simo...@microsoft.com> Date: Fri Oct 26 12:31:55 2012 +0100 Test Trac #7328 and #7332 >--------------------------------------------------------------- tests/polykinds/T7328.hs | 8 ++++++++ tests/polykinds/T7328.stderr | 7 +++++++ .../should_compile => polykinds}/T7332.hs | 12 ++---------- tests/polykinds/all.T | 2 ++ 4 files changed, 19 insertions(+), 10 deletions(-) diff --git a/tests/polykinds/T7328.hs b/tests/polykinds/T7328.hs new file mode 100644 index 0000000..3e51875 --- /dev/null +++ b/tests/polykinds/T7328.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE PolyKinds, GADTs #-} + +module T7328 where + +data Proxy a + +class Foo a where + foo :: a ~ f i => Proxy (Foo f) diff --git a/tests/polykinds/T7328.stderr b/tests/polykinds/T7328.stderr new file mode 100644 index 0000000..6151c5a --- /dev/null +++ b/tests/polykinds/T7328.stderr @@ -0,0 +1,7 @@ + +T7328.hs:8:34: + Kind occurs check + The first argument of `Foo' should have kind `k0', + but `f' has kind `k1 -> k0' + In the type `a ~ f i => Proxy (Foo f)' + In the class declaration for `Foo' diff --git a/tests/indexed-types/should_compile/T7332.hs b/tests/polykinds/T7332.hs similarity index 76% copy from tests/indexed-types/should_compile/T7332.hs copy to tests/polykinds/T7332.hs index 0649741..647dd93 100644 --- a/tests/indexed-types/should_compile/T7332.hs +++ b/tests/polykinds/T7332.hs @@ -4,11 +4,10 @@ {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE MagicHash #-} -module Oleg where +module T7332 where -import GHC.Exts hiding( build ) +import GHC.Exts( IsString(..) ) import Data.Monoid newtype DC d = DC d @@ -37,13 +36,6 @@ tspan = build (id :: DC d -> DC d) mempty foo = tspan "aa" -{- Need (Monoid d, Build (DC d) (a -> t), BuildR (a -> t) ~ DC d, IsString a) - -BuildR (a -> t) = BuildR t -Build (DC d) (a -> t) ===> (Build (DC d) t, a ~ DC d) - - -} - foo1 = tspan (tspan "aa") bar = tspan "aa" :: DC String diff --git a/tests/polykinds/all.T b/tests/polykinds/all.T index 33f8ffe..701538e 100644 --- a/tests/polykinds/all.T +++ b/tests/polykinds/all.T @@ -73,3 +73,5 @@ test('T7230', normal, compile_fail,['']) test('T7238', normal, compile,['']) test('T7278', normal, compile_fail,['']) test('Holdermans', normal, compile_fail,['']) +test('T7328', normal, compile_fail,['']) +test('T7332', normal, compile,['']) _______________________________________________ Cvs-ghc mailing list Cvs-ghc@haskell.org http://www.haskell.org/mailman/listinfo/cvs-ghc