[commit: testsuite] master: Test Trac #8357 (06afa91)

git at git.haskell.org git
Thu Oct 3 14:40:27 UTC 2013


Repository : ssh://git at git.haskell.org/testsuite

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/06afa916d4f76e58903bdf133567d28499780f68/testsuite

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

commit 06afa916d4f76e58903bdf133567d28499780f68
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Thu Oct 3 15:40:13 2013 +0100

    Test Trac #8357


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

06afa916d4f76e58903bdf133567d28499780f68
 tests/ghci/scripts/T8357.hs     |   32 ++++++++++++++++++++++++++++++++
 tests/ghci/scripts/T8357.script |    4 ++++
 tests/ghci/scripts/T8357.stdout |    3 +++
 tests/ghci/scripts/all.T        |    1 +
 4 files changed, 40 insertions(+)

diff --git a/tests/ghci/scripts/T8357.hs b/tests/ghci/scripts/T8357.hs
new file mode 100644
index 0000000..29fe7a8
--- /dev/null
+++ b/tests/ghci/scripts/T8357.hs
@@ -0,0 +1,32 @@
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE KindSignatures #-}
+{-# LANGUAGE TypeOperators #-}
+module T8357 where
+
+import GHC.TypeLits 
+
+data (:::) (sy :: Symbol) ty 
+data Key (sy :: Symbol) 
+data Rec (rs :: [*])
+
+(*=) :: Key sy -> ty -> Rec '[sy ::: ty]
+(*=) = undefined
+
+(.*.) :: (Union xs ys ~ rs) => Rec xs -> Rec ys -> Rec rs
+(.*.) = undefined
+
+type family Union (xs :: [*]) (ys :: [*]) :: [*]  where
+    Union ((sy ::: t) ': xs) ys = (sy ::: t) ': Union xs ys
+    Union '[] ys = ys
+
+
+fFoo :: Key "foo"
+fFoo = undefined
+
+fBar :: Key "bar"
+fBar = undefined
+
+foo = fFoo *= "foo"
+bar = fBar *= "bar"
+both = foo .*. bar
\ No newline at end of file
diff --git a/tests/ghci/scripts/T8357.script b/tests/ghci/scripts/T8357.script
new file mode 100644
index 0000000..975aa37
--- /dev/null
+++ b/tests/ghci/scripts/T8357.script
@@ -0,0 +1,4 @@
+:l T8357.hs
+:t foo
+:t bar
+:t both
diff --git a/tests/ghci/scripts/T8357.stdout b/tests/ghci/scripts/T8357.stdout
new file mode 100644
index 0000000..7975d1f
--- /dev/null
+++ b/tests/ghci/scripts/T8357.stdout
@@ -0,0 +1,3 @@
+foo :: Rec '["foo" ::: [Char]]
+bar :: Rec '["bar" ::: [Char]]
+both :: Rec '["foo" ::: [Char], "bar" ::: [Char]]
diff --git a/tests/ghci/scripts/all.T b/tests/ghci/scripts/all.T
index 06ba3bb..d5b9e2c 100755
--- a/tests/ghci/scripts/all.T
+++ b/tests/ghci/scripts/all.T
@@ -155,3 +155,4 @@ test('T8116', normal, ghci_script, ['T8116.script'])
 test('T8113', normal, ghci_script, ['T8113.script'])
 test('T8172', normal, ghci_script, ['T8172.script'])
 test('T8215', normal, ghci_script, ['T8215.script'])
+test('T8357', normal, ghci_script, ['T8357.script'])




More information about the ghc-commits mailing list