summaryrefslogtreecommitdiff
path: root/testsuite/tests/unboxedsums/T20858.hs
blob: cada16076433ddd9c60357a66cb89ad5de1c1cb2 (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
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ExplicitForAll #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE StandaloneKindSignatures #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UnboxedSums #-}

module T20858 where

import Data.Kind
  ( Type )
import GHC.Exts
  ( Double#, Int#, Word# )

type GetFunKind :: k -> Type
type family GetFunKind x where
  forall arg_k res_k (a :: arg_k -> res_k) (b :: arg_k). GetFunKind (a b) = arg_k -> res_k

type GetFun :: forall res_k. forall (x :: res_k) -> GetFunKind x
type family GetFun x where
  GetFun (a b) = a

type S1 = GetFun (# Int# | Double# | Word# #)
type S2 = GetFun S1
type S3 = GetFun S2