[commit: ghc] master: Test Trac #12133 (6cedef0)

git at git.haskell.org git at git.haskell.org
Tue Jul 5 15:20:13 UTC 2016


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/6cedef01e00e95517a546a72592ba6ff07bac605/ghc

>---------------------------------------------------------------

commit 6cedef01e00e95517a546a72592ba6ff07bac605
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Tue Jul 5 16:23:01 2016 +0100

    Test Trac #12133


>---------------------------------------------------------------

6cedef01e00e95517a546a72592ba6ff07bac605
 testsuite/tests/typecheck/should_compile/T12133.hs | 68 ++++++++++++++++++++++
 testsuite/tests/typecheck/should_compile/all.T     |  1 +
 2 files changed, 69 insertions(+)

diff --git a/testsuite/tests/typecheck/should_compile/T12133.hs b/testsuite/tests/typecheck/should_compile/T12133.hs
new file mode 100644
index 0000000..f2502a7
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/T12133.hs
@@ -0,0 +1,68 @@
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE ConstraintKinds #-}
+{-# LANGUAGE GADTs #-}
+{-# LANGUAGE ImplicitParams #-}
+{-# LANGUAGE KindSignatures #-}
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE TypeOperators #-}
+
+module T12133 where
+
+import           GHC.Classes (IP(..))
+import           GHC.Exts (Constraint)
+
+-- | From "Data.Constraint":
+data Dict :: Constraint -> * where Dict :: a => Dict a
+
+newtype a :- b = Sub (a => Dict b)
+
+infixl 1 \\ -- required comment
+
+(\\) :: a => (b => r) -> (a :- b) -> r
+r \\ Sub Dict = r
+
+-- | GHC 7.10.2 type checks this function but GHC 8.0.1 does not unless
+-- you modify this example in one of the following ways:
+--
+--   * uncomments the type signature for 'Sub'
+--
+--   * flatten the nested pairs of constraints into a triple of constraints
+--
+--   * replace 'IP sym ty' with 'c9', where 'c9' is a new constraint variable.
+--
+-- The error message is listed below.
+foo :: forall c1 c2 c3 sym ty
+    .  (c1, c2) :- c3
+    -> (c1, (IP sym ty, c2)) :- (IP sym ty, c3)
+foo sp = ( Sub
+--           :: ((c1, (IP sym ty, c2)) => Dict (IP sym ty, c3))
+--              -> (c1, ((IP sym ty), c2)) :- (IP sym ty, c3)
+         )
+         ( (Dict \\ sp) :: Dict (IP sym ty, c3) )
+
+{- Compiler error message:
+
+GHCi, version 8.0.1: http://www.haskell.org/ghc/  :? for help
+[1 of 1] Compiling T                ( t.hs, interpreted )
+
+t.hs:44:13: error:
+    • Could not deduce: IP sym ty arising from a use of ‘Dict’
+      from the context: (c1, (IP sym ty, c2))
+        bound by a type expected by the context:
+                   (c1, (IP sym ty, c2)) => Dict (IP sym ty, c3)
+        at t.hs:(40,10)-(44,49)
+      or from: c3
+        bound by a type expected by the context:
+                   c3 => Dict (IP sym ty, c3)
+        at t.hs:44:13-22
+    • In the first argument of ‘(\\)’, namely ‘Dict’
+      In the first argument of ‘Sub’, namely
+        ‘((Dict \\ sp) :: Dict (IP sym ty, c3))’
+      In the expression: (Sub) ((Dict \\ sp) :: Dict (IP sym ty, c3))
+    • Relevant bindings include
+        foo :: (c1, c2) :- c3 -> (c1, (IP sym ty, c2)) :- (IP sym ty, c3)
+          (bound at t.hs:40:1)
+Failed, modules loaded: none.
+-}
\ No newline at end of file
diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T
index 33d91d1..7333ffb 100644
--- a/testsuite/tests/typecheck/should_compile/all.T
+++ b/testsuite/tests/typecheck/should_compile/all.T
@@ -530,3 +530,4 @@ test('T11974', normal, compile, [''])
 test('T12067', extra_clean(['T12067a.hi', 'T12067a.o']),
      multimod_compile, ['T12067', '-v0'])
 test('T12185', normal, compile, [''])
+test('T12133', normal, compile, [''])



More information about the ghc-commits mailing list