Heterogeneous lists are one of the examples given for the new dependent type facility of ghc 7.6:
data HList :: [*] -> * where
HNil :: HList '[]
HCons:: a -> HList t -> HList (a ': t)
The example list "li" compiles fine:
li = HCons "Int: " (HCons 234 (HCons "Integer: " (HCons 129877645 HNil)))
Obviously we would like HList to be in the Show class, but I can only come up with the following working class instantiation that uses mutually recursive constraints (superclasses):
instance Show (HList '[]) where
show HNil = "[]"
instance (Show a, Show' (HList t)) => Show (HList (a ': t)) where
show l = "[" ++ show' l ++ "]"
class Show' a where
show' :: a -> String
instance Show' (HList '[]) where
show' HNil = ""
instance (Show a, Show' (HList t)) => Show' (HList (a ': t)) where
show' (HCons h l) = case l of
HNil -> show h
HCons _ _ -> show h ++ ", " ++ (show' l)
The code compiles fine and li is shown properly. Compile flags needed are:
{-# LANGUAGE DataKinds, TypeOperators, KindSignatures,
FlexibleContexts, GADTs, FlexibleInstances #-}
I tried many variants of the following far more direct definition, but it doesn't compile without me being able to understand the ghc error messages:
instance Show (HList '[]) where
show HNil = "[]"
instance (Show a, Show (HList t)) => Show (HList (a ': t)) where
show l = "[" ++ (show' l) ++ "]" where
show' (HCons h s) = case s of
HNil -> show h
HCons _ _ -> show h ++ ", " ++ (show' s)
Some Haskell / ghc specialist might understand why this can't work and I would be happy to hear the reason.
Thank you
Hans Peter
Thank you, hammar, for your two nice working examples, improving on my first example.
But I still don't understand why my second example doesn't work. You say that "... show' only knows how to show the current element type and not the remaining ones." But wouldn't that comment not also apply in the following (working) code:
instance Show (HList '[]) where show HNil = ""
instance (Show a, Show (HList t)) => Show (HList (a ': t)) where
show (HCons h t) = case t of
HNil -> show h
HCons _ _ -> show h ++ ", " ++ (show t)
show' (HCons h HNil) = show h
,show' (HCons h s) = show h ++ ", " ++ show' s
? – Premedicalshow' :: forall a t. (Show a, Show (HList t)) => HList (a ': t) -> String
doesn't provide any constraint that says that you can show the next element in the list. Defining it likeHCons _ _ -> show h ++ ", " ++ show s
would work but won't be formatted the same as your original example. – SuperaddShow a, Show (HList t))
constraint states that you canshow
the head and tail of the list. It doesn't say anything about the Nth element (where N > 0), just the head and tail. Type families with constraint kinds (Hammar's example) or a helper type class (your alternative solution) are two ways around this. – Superadd