summaryrefslogtreecommitdiff
path: root/testsuite/tests/rep-poly/T20363.hs
blob: a28e483ffbc6f3da33262111def7ed49d54b109b (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
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