summaryrefslogtreecommitdiff
path: root/testsuite/tests/polykinds/T7973.hs
blob: 0053858d8149e1c8b787a1e561655c98256f0c78 (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
{-# LANGUAGE DataKinds, PolyKinds, KindSignatures #-}
{-# LANGUAGE ExistentialQuantification, UndecidableInstances, TypeFamilies,
             FlexibleContexts #-}

module Test where

import Data.Kind (Type)

-- Kind-level proxies.
data {-kind-} K (a :: Type) = KP

-- A type with 1 kind-polymorphic type argument.
data T (n :: k)

-- A type with 1 kind argument.
data F (kp :: K k)

-- A class with 1 kind argument.
class (kp ~ KP) => C (kp :: K k) where
  f :: T (a :: k) -> F kp

-- A type with 1 kind argument.
-- Contains an existentially quantified type-variable of this kind.
data SomeT (kp :: K k) = forall (n :: k). Mk (T n)

-- Show `SomeT` by converting it to `F`, using `C`.
instance (C kp, Show (F kp)) => Show (SomeT kp) where
  show (Mk x) = show (f x)