[commit: ghc] ghc-8.0: Test Trac #11379 (500ddd3)

git at git.haskell.org git at git.haskell.org
Mon Jan 18 12:24:37 UTC 2016


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

On branch  : ghc-8.0
Link       : http://ghc.haskell.org/trac/ghc/changeset/500ddd33af85b4d91c9cee5568c11b56a372d1a7/ghc

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

commit 500ddd33af85b4d91c9cee5568c11b56a372d1a7
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Mon Jan 18 11:53:05 2016 +0000

    Test Trac #11379
    
    (cherry picked from commit 8e50301f7514751fc5c1fcc0e2847a49041ca2e7)


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

500ddd33af85b4d91c9cee5568c11b56a372d1a7
 testsuite/tests/typecheck/should_compile/T11379.hs | 36 ++++++++++++++++++++++
 testsuite/tests/typecheck/should_compile/all.T     |  1 +
 2 files changed, 37 insertions(+)

diff --git a/testsuite/tests/typecheck/should_compile/T11379.hs b/testsuite/tests/typecheck/should_compile/T11379.hs
new file mode 100644
index 0000000..35e27a5
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/T11379.hs
@@ -0,0 +1,36 @@
+{-# LANGUAGE ExistentialQuantification, RankNTypes, MultiParamTypeClasses,
+              FunctionalDependencies, FlexibleInstances, FlexibleContexts
+ #-}
+
+module XMonad.Layout.MultiToggle where
+
+import Data.Typeable
+
+-- This appears to be the culprit
+expand :: (HList ts a) => MultiToggleS ts l a -> MultiToggle ts l a
+expand (MultiToggleS b ts) =
+    resolve ts id
+        (\x mt -> let g = transform' x in mt{ currLayout = g $ currLayout mt })
+        (MultiToggle (EL b id) ts)
+
+class (Typeable t) => Transformer t a | t -> a where
+    transform :: t
+              -> l a
+              -> (forall l'. l' a -> (l' a -> l a) -> b)
+              -> b
+
+data  EL l a = forall l'. EL (l' a) (l' a -> l a)
+
+transform' :: (Transformer t a) => t -> EL l a -> EL l a
+transform' t (EL l det) = undefined
+
+data MultiToggleS ts l a = MultiToggleS (l a) ts
+                         deriving (Read, Show)
+
+data MultiToggle ts l a = MultiToggle{
+    currLayout :: EL l a,
+    transformers :: ts
+    }
+
+class HList c a where
+    resolve :: c -> b -> (forall t. (Transformer t a) => t -> b) -> b
diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T
index bf43716..46ab53b 100644
--- a/testsuite/tests/typecheck/should_compile/all.T
+++ b/testsuite/tests/typecheck/should_compile/all.T
@@ -488,3 +488,4 @@ test('T11237', normal, compile, [''])
 test('T10592', normal, compile, [''])
 test('T11305', normal, compile, [''])
 test('T11254', normal, compile, [''])
+test('T11379', normal, compile, [''])



More information about the ghc-commits mailing list