summaryrefslogtreecommitdiff
path: root/testsuite/tests/indexed-types/should_fail/T2664.hs
diff options
context:
space:
mode:
Diffstat (limited to 'testsuite/tests/indexed-types/should_fail/T2664.hs')
-rw-r--r--testsuite/tests/indexed-types/should_fail/T2664.hs31
1 files changed, 31 insertions, 0 deletions
diff --git a/testsuite/tests/indexed-types/should_fail/T2664.hs b/testsuite/tests/indexed-types/should_fail/T2664.hs
new file mode 100644
index 0000000000..d5b04a6380
--- /dev/null
+++ b/testsuite/tests/indexed-types/should_fail/T2664.hs
@@ -0,0 +1,31 @@
+{-# LANGUAGE EmptyDataDecls, TypeFamilies, TypeOperators, ScopedTypeVariables #-}
+module Overflow where
+import Control.Concurrent
+
+data (:*:) a b
+data (:+:) a b
+
+data family PChan a
+data instance PChan (a :+: b) = E (IO (PChan a)) (IO (PChan b))
+newtype instance PChan (a :*: b) = O (IO (Either (PChan a) (PChan b)))
+
+type family Dual a
+type instance Dual (a :+: b) = Dual a :*: Dual b
+type instance Dual (a :*: b) = Dual a :+: Dual b
+
+class Connect s where
+ newPChan :: (s ~ Dual c, c ~ Dual s) => IO (PChan s, PChan c)
+
+pchoose :: (t -> a) -> MVar a -> IO (t,b) -> IO b
+pchoose = undefined
+
+instance (Connect a, Connect b) => Connect (a :*: b) where
+ newPChan = do
+ v <- newEmptyMVar
+
+ -- This version is in T2664a
+ -- correct implementation:
+ -- return (O $ takeMVar v, E (pchoose Left v newPChan) (pchoose Right v newPChan))
+
+ -- type error leads to stack overflow (even without UndecidableInstances!)
+ return (O $ takeMVar v, E (pchoose Right v newPChan) (pchoose Left v newPChan))