
On Fri, 2008-12-05 at 01:27 +0300, Dmitri O.Kondratiev wrote:
I am trying to define instance Show[MyType] so show (x:xs :: MyType) would return a single string where substrings corresponding to list elements will be separated by "\n". This would allow pretty printing of MyType list in several lines instead of one, as default Show does for lists.
For example:
data ShipInfo = Ship { name :: String, kind :: String, canons :: Int } deriving Show
s1 = Ship {name ="HMS Fly", kind = "sloop", canons=16} s2 = Ship {name ="HMS Surprise", kind = "frigate", canons=42}
-- Yet when I try to define: instance (Show ShipInfo) => Show [ShipInfo] where show (x:xs) = "<" ++ show x ++ ">" ++ show xs
The context on this is borked: you already know Show ShipInfo, so you don't need to assume it here.
-- I get this error: Illegal instance declaration for `Show [ShipInfo]' (The instance type must be of form (T a b c) where T is not a synonym, and a,b,c are distinct type variables)
Read this error again. Your instance is for the type `[] ShipInfo', which does not have the form GHC listed for you. The instance in GHC.Show (don't import it from there! Import it from Prelude, instead) is for a type of the form `[] a', which does have that form. Now, in this case, you don't need to define Show ([ShipInfo]), because the instance for Show [a] already does what you want; you just need to define an explicit instance for Show ShipInfo and over-ride the showList method. If you really, really wanted to define Show [ShipInfo], then putting {-# LANGUAGE FlexibleInstances, OverlappingInstances #-} at the beginning of your file would work. At the cost of using overlapping instances, of course. jcc