Repository : ssh://darcs.haskell.org//srv/darcs/testsuite

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/fa6bb222739634e5a6a6abc6b4831c2a2b18a362

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

commit fa6bb222739634e5a6a6abc6b4831c2a2b18a362
Author: Dimitrios.Vytiniotis <[email protected]>
Date:   Tue Apr 10 02:12:13 2012 +0100

    Adding test case for polytype decomposition in the constraint solver.

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

 tests/typecheck/should_compile/PolytypeDecomp.hs |   32 ++++++++++++++++++++++
 tests/typecheck/should_compile/all.T             |    2 +
 2 files changed, 34 insertions(+), 0 deletions(-)

diff --git a/tests/typecheck/should_compile/PolytypeDecomp.hs 
b/tests/typecheck/should_compile/PolytypeDecomp.hs
new file mode 100644
index 0000000..69e4fb3
--- /dev/null
+++ b/tests/typecheck/should_compile/PolytypeDecomp.hs
@@ -0,0 +1,32 @@
+{-# LANGUAGE TypeFamilies, LiberalTypeSynonyms, ImpredicativeTypes #-}
+module PolyTypeDecomp where 
+
+
+{- The purpose of this test is to check if decomposition of wanted 
+   equalities in the /constraint solver/ (vs. the unifier) works properly.
+   Unfortunately most equalities between polymorphic types are converted to 
+   implication constraints early on in the unifier, so we have to make things
+   a bit more convoluted by introducing the myLength function. The wanted 
+   constraints we get for this program are:
+      [forall a. Maybe a] ~ Id alpha
+      [forall a. F [a]]   ~ Id alpha 
+   Which, /after reactions/ should create a fresh implication: 
+      forall a. Maybe a ~ F [a]
+   that is perfectly soluble.
+-}
+ 
+type family F a
+type instance F [a] = Maybe a 
+
+type family Id a 
+type instance Id a = a
+
+f :: [forall a. F [a]]
+f = undefined
+
+
+g :: [forall a. Maybe a] -> Int
+g x = myLength [x,f]
+
+myLength :: [Id a] -> Int 
+myLength = undefined
diff --git a/tests/typecheck/should_compile/all.T 
b/tests/typecheck/should_compile/all.T
index 5fcd89f..918d5c8 100644
--- a/tests/typecheck/should_compile/all.T
+++ b/tests/typecheck/should_compile/all.T
@@ -375,3 +375,5 @@ test('T3108', normal, compile, [''])
 
 test('T5792',normal,run_command,
      ['$MAKE -s --no-print-directory T5792'])
+
+test('PolytypeDecomp', normal, compile, [''])
\ No newline at end of file



_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to