summaryrefslogtreecommitdiff
path: root/testsuite/tests/indexed-types/should_compile/T9747.hs
blob: 05b43976301614ef913cd5988b95e16e0a110d69 (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
{-# LANGUAGE ConstraintKinds, DataKinds, GADTs, TypeFamilies, TypeOperators #-}
module T9747 where
import Data.List (intercalate)
import Data.Proxy
import GHC.Prim (Constraint)

data HList :: [*] -> * where
  Nil :: HList '[]
  Cons :: a -> HList as -> HList (a ': as)

type family HListAll (c :: * -> Constraint) (ts :: [*]) :: Constraint where
  HListAll c '[] = ()
  HListAll c (t ': ts) = (c t, HListAll c ts)

showHList :: HListAll Show ts => HList ts -> String
showHList = ("[" ++ ) . (++"]") . intercalate ", " . go
  where
    go :: HListAll Show ts => HList ts -> [String]
    go Nil = []
    go (Cons x xs) = show x : go xs

-- Things work okay up to this point
test :: String
test = showHList (Cons (2::Int)
                 (Cons (3.1 :: Float)
                 (Cons 'c' Nil)))

type family ConFun (t :: *) :: * -> Constraint
data Tag
type instance ConFun Tag = Group

class (Show a, Eq a, Ord a) => Group a

-- This is notionally similar to showHList
bar :: HListAll (ConFun l) ts => Proxy l -> HList ts -> ()
bar _ _ = ()

baz :: (ConFun l a, ConFun l b) => Proxy l -> HList [a,b] -> ()
baz = bar