[commit: ghc] master: Test case for #7961. (68f198f)
git at git.haskell.org
git at git.haskell.org
Sat Dec 12 02:53:15 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/68f198f50ca6439957a65a95ce6e087d43b56eed/ghc
>---------------------------------------------------------------
commit 68f198f50ca6439957a65a95ce6e087d43b56eed
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date: Fri Dec 11 21:51:37 2015 -0500
Test case for #7961.
Test case: dependent/shoud_compile/TypeLevelVec
>---------------------------------------------------------------
68f198f50ca6439957a65a95ce6e087d43b56eed
.../tests/dependent/should_compile/TypeLevelVec.hs | 26 ++++++++++++++++++++++
testsuite/tests/dependent/should_compile/all.T | 1 +
2 files changed, 27 insertions(+)
diff --git a/testsuite/tests/dependent/should_compile/TypeLevelVec.hs b/testsuite/tests/dependent/should_compile/TypeLevelVec.hs
new file mode 100644
index 0000000..19f605c
--- /dev/null
+++ b/testsuite/tests/dependent/should_compile/TypeLevelVec.hs
@@ -0,0 +1,26 @@
+{-# LANGUAGE TypeInType, UnicodeSyntax, GADTs, NoImplicitPrelude,
+ TypeOperators, TypeFamilies #-}
+{-# OPTIONS_GHC -fno-warn-unticked-promoted-constructors #-}
+
+module TypeLevelVec where
+
+import Data.Kind
+
+data ℕ ∷ Type where
+ O ∷ ℕ
+ S ∷ ℕ → ℕ
+
+type family x + y where
+ O + n = n
+ S m + n = S (m + n)
+infixl 5 +
+
+data Vec ∷ ℕ → Type → Type where
+ Nil ∷ Vec O a
+ (:>) ∷ a → Vec n a → Vec (S n) a
+infixr 8 :>
+
+type family (x ∷ Vec n a) ++ (y ∷ Vec m a) ∷ Vec (n + m) a where
+ Nil ++ y = y
+ (x :> xs) ++ y = x :> (xs ++ y)
+infixl 5 ++
diff --git a/testsuite/tests/dependent/should_compile/all.T b/testsuite/tests/dependent/should_compile/all.T
index 0f231db..1724ff6 100644
--- a/testsuite/tests/dependent/should_compile/all.T
+++ b/testsuite/tests/dependent/should_compile/all.T
@@ -8,3 +8,4 @@ test('RAE_T32b', only_ways('normal'), compile, [''])
test('KindLevels', normal, compile, [''])
test('RaeBlogPost', normal, compile, [''])
test('mkGADTVars', normal, compile, [''])
+test('TypeLevelVec',normal,compile, [''])
More information about the ghc-commits
mailing list