summaryrefslogtreecommitdiff
path: root/testsuite/tests/typecheck/should_compile/T14451.hs
diff options
context:
space:
mode:
authorRyan Scott <ryan.gl.scott@gmail.com>2018-12-03 11:34:02 -0500
committerRyan Scott <ryan.gl.scott@gmail.com>2018-12-03 11:34:02 -0500
commitaef5d82543bb642a65f63e1f05f245b9cddafd8c (patch)
tree0a3ba58ffbab5840d53d6dac43717deceeff9aba /testsuite/tests/typecheck/should_compile/T14451.hs
parenta46511a88e719d990285f06b29a38839b3e0a0bf (diff)
downloadhaskell-aef5d82543bb642a65f63e1f05f245b9cddafd8c.tar.gz
Add test cases for #7503, #14451
At some point between 8.4 and 8.6, two things were fixed: * The entirety of #14451. * One of the test cases in #7503. I've added this as T7503a. The other test case from that ticket still does /not/ work, so we'll have to add T7503b some other day.
Diffstat (limited to 'testsuite/tests/typecheck/should_compile/T14451.hs')
-rw-r--r--testsuite/tests/typecheck/should_compile/T14451.hs28
1 files changed, 28 insertions, 0 deletions
diff --git a/testsuite/tests/typecheck/should_compile/T14451.hs b/testsuite/tests/typecheck/should_compile/T14451.hs
new file mode 100644
index 0000000000..a67ce74537
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/T14451.hs
@@ -0,0 +1,28 @@
+{-# Language KindSignatures, TypeOperators, PolyKinds, TypeOperators, ConstraintKinds, TypeFamilies, DataKinds, TypeInType, GADTs, AllowAmbiguousTypes, InstanceSigs, RankNTypes, UndecidableInstances #-}
+module T14451 where
+
+import Data.Kind
+
+data TyFun :: Type -> Type -> Type
+
+type a ~> b = TyFun a b -> Type
+
+type Cat ob = ob -> ob -> Type
+
+type family
+ Apply (f :: a ~> b) (x :: a) :: b where
+ Apply (CompSym2 f g) a = Comp f g a
+
+data CompSym2 :: (b ~> c) -> (a ~> b) -> (a ~> c)
+
+type a·b = Apply a b
+
+class Varpi (f :: i ~> j) where
+ type Dom (f :: i ~> j) :: Cat i
+ type Cod (f :: i ~> j) :: Cat j
+
+ varpa :: Dom f a a' -> Cod f (f·a) (f·a')
+
+type family
+ Comp (f::k1 ~> k) (g::k2 ~> k1) (a::k2) :: k where
+ Comp f g a = f · (g · a)