summaryrefslogtreecommitdiff
path: root/testsuite/tests/rep-poly/T20363.hs
diff options
context:
space:
mode:
Diffstat (limited to 'testsuite/tests/rep-poly/T20363.hs')
-rw-r--r--testsuite/tests/rep-poly/T20363.hs48
1 files changed, 48 insertions, 0 deletions
diff --git a/testsuite/tests/rep-poly/T20363.hs b/testsuite/tests/rep-poly/T20363.hs
new file mode 100644
index 0000000000..a28e483ffb
--- /dev/null
+++ b/testsuite/tests/rep-poly/T20363.hs
@@ -0,0 +1,48 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE StandaloneKindSignatures #-}
+{-# LANGUAGE TypeApplications #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE UnboxedTuples #-}
+{-# LANGUAGE UnliftedNewtypes #-}
+
+module T20363 where
+
+import GHC.Exts
+
+data Nat = Zero | Suc Nat
+
+type NestedTupleRep :: Nat -> RuntimeRep -> RuntimeRep
+type family NestedTupleRep n r where
+ NestedTupleRep Zero r = TupleRep '[]
+ NestedTupleRep (Suc n) r = TupleRep '[ r, NestedTupleRep n r ]
+
+type NestedTuple
+ :: forall ( n :: Nat )
+ -> forall ( r :: RuntimeRep )
+ . forall ( a :: TYPE r )
+ -> TYPE ( NestedTupleRep n r )
+type family NestedTuple n a where
+ NestedTuple Zero @r a = (# #)
+ NestedTuple (Suc n) @r a = (# a, NestedTuple n @r a #)
+
+type NestedTupleNT
+ :: forall ( n :: Nat )
+ -> forall ( r :: RuntimeRep )
+ . forall ( a :: TYPE r )
+ -> TYPE ( NestedTupleRep n r )
+newtype NestedTupleNT n (a :: TYPE r) = MkNT ( NestedTuple n a )
+
+test1a :: NestedTuple Zero Addr# -> Int
+test1a (# #) = 0
+
+test2a :: NestedTuple (Suc Zero) Addr# -> Addr#
+test2a (# i, (# #) #) = i
+
+test1b :: NestedTupleNT Zero Addr# -> Int
+test1b ( MkNT (# #) ) = 0
+
+test2b :: NestedTupleNT (Suc Zero) Addr# -> Addr#
+test2b ( MkNT (# i, (# #) #) ) = i