summaryrefslogtreecommitdiff
path: root/testsuite/tests/ghci/scripts
diff options
context:
space:
mode:
authorSimon Peyton Jones <simonpj@microsoft.com>2013-10-03 15:40:13 +0100
committerSimon Peyton Jones <simonpj@microsoft.com>2013-10-03 15:40:13 +0100
commit80d2a0850a787de1b10f4e732bb20bc87e779814 (patch)
tree17e57858478731aca2da7213d5a70682ac263841 /testsuite/tests/ghci/scripts
parentd3710922b55e0635e099ea10a3bf5ab2824e9fff (diff)
downloadhaskell-80d2a0850a787de1b10f4e732bb20bc87e779814.tar.gz
Test Trac #8357
Diffstat (limited to 'testsuite/tests/ghci/scripts')
-rw-r--r--testsuite/tests/ghci/scripts/T8357.hs32
-rw-r--r--testsuite/tests/ghci/scripts/T8357.script4
-rw-r--r--testsuite/tests/ghci/scripts/T8357.stdout3
-rwxr-xr-xtestsuite/tests/ghci/scripts/all.T1
4 files changed, 40 insertions, 0 deletions
diff --git a/testsuite/tests/ghci/scripts/T8357.hs b/testsuite/tests/ghci/scripts/T8357.hs
new file mode 100644
index 0000000000..29fe7a85bb
--- /dev/null
+++ b/testsuite/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/testsuite/tests/ghci/scripts/T8357.script b/testsuite/tests/ghci/scripts/T8357.script
new file mode 100644
index 0000000000..975aa3761f
--- /dev/null
+++ b/testsuite/tests/ghci/scripts/T8357.script
@@ -0,0 +1,4 @@
+:l T8357.hs
+:t foo
+:t bar
+:t both
diff --git a/testsuite/tests/ghci/scripts/T8357.stdout b/testsuite/tests/ghci/scripts/T8357.stdout
new file mode 100644
index 0000000000..7975d1f1a1
--- /dev/null
+++ b/testsuite/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/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T
index 06ba3bbb96..d5b9e2cf05 100755
--- a/testsuite/tests/ghci/scripts/all.T
+++ b/testsuite/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'])