summaryrefslogtreecommitdiff
path: root/testsuite/tests/simplCore/should_compile/T18120.hs
blob: 0a2ea98638212d8bf9b294d39fb60f91668c076b (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
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE UndecidableSuperClasses #-}
module Bug where

import Data.Kind

type family
  AllF (c :: k -> Constraint) (xs :: [k]) :: Constraint where
  AllF _c '[]       = ()
  AllF  c (x ': xs) = (c x, All c xs)

class (AllF c xs, SListI xs) => All (c :: k -> Constraint) (xs :: [k]) where
instance All c '[] where
instance (c x, All c xs) => All c (x ': xs) where

class Top x
instance Top x

type SListI = All Top

class All SListI (Code a) => Generic (a :: Type) where
  type Code a :: [[Type]]

data T = MkT Int
instance Generic T where
  type Code T = '[ '[Int] ]