
The problem is that Engine *could* be made an instance of Show (remember that any user of the module can create that instance later). What you need is the overlappinginstances extension: {-# LANGUAGE OverlappingInstances #-} With this extension, the most specific instance will be used, i.e. "instance TShow Engine" for Enginge's, no matter if it is an instance of Show. /Tobias ________________________________ From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of John Ky Sent: den 8 december 2008 13:32 To: Haskell Cafe Subject: [Haskell-cafe] Overlapping instances Hi, I've got the following code which tries to implement a TShow class, which is equivalent to Show, except it is supposed to work on TVar types as well. import GHC.Conc createEngine :: String -> Int -> Int -> IO Engine createEngine name major minor = do tUsers <- newTVarIO [] return $ Engine { engineName = name , version = EngineVersion { major = major , minor = minor } , users = tUsers } class TShow a where tshow :: a -> IO String instance Show (TVar a) where show a = "%" instance (Show a) => TShow a where tshow a = return $ show a instance (Show a) => TShow (TVar a) where tshow ta = do a <- atomically (readTVar ta) return $ show a data User = User { userName :: String } deriving Show data EngineVersion = EngineVersion { major :: Int , minor :: Int } deriving Show data Engine = Engine { engineName :: String , version :: EngineVersion , users :: TVar [User] } instance TShow Engine where tshow a = do users <- atomically (readTVar (users a)) return $ "Engine { " ++ "engineName = " ++ show (engineName a) ++ ", " ++ "version = " ++ show (version a) ++ ", " ++ "users = %" ++ show users ++ " }" When I run it however, I get this: *Main> te <- createEngine "Hello" 1 2 *Main> s <- tshow te <interactive>:1:5: Overlapping instances for TShow Engine arising from a use of `tshow' at <interactive>:1:5-12 Matching instances: instance (Show a) => TShow a -- Defined at fxmain.hs:(26,0)-(27,27) instance TShow Engine -- Defined at fxmain.hs:(51,0)-(58,41) In a stmt of a 'do' expression: s <- tshow te I'm not seeing how instance (Show a) => TShow a in the above error message is applicable here since Engine is not an instance of Show. Why is it complaining? Thanks, -John