Your problem isn't actually the same as in that question. In the question you linked to, Derek Thurn had a function which he knew took a Set a
, but couldn't pattern-match. In your case, you're writing a function which will take any a
which has an instance of Show
; you can't tell what type you're looking at at runtime, and can only rely on the functions which are available to any Show
able type. If you want to have a function do different things for different data types, this is known as ad-hoc polymorphism, and is supported in Haskell with type classes like Show
. (This is as opposed to parametric polymorphism, which is when you write a function like head (x:_) = x
which has type head :: [a] -> a
; the unconstrained universal a
is what makes that parametric instead.) So to do what you want, you'll have to create your own type class, and instantiate it when you need it. However, it's a little more complicated than usual, because you want to make everything that's part of Show
implicitly part of your new type class. This requires some potentially dangerous and probably unnecessarily powerful GHC extensions. Instead, why not simplify things? You can probably figure out the subset of types which you actually need to print in this manner. Once you do that, you can write the code as follows:
{-# LANGUAGE TypeSynonymInstances #-}
module GraphvizTypeclass where
import qualified Data.Map as M
import Data.Map (Map)
import Data.List (intercalate) -- For output formatting
surround :: String -> String -> String -> String
surround before after = (before ++) . (++ after)
squareBrackets :: String -> String
squareBrackets = surround "[" "]"
quoted :: String -> String
quoted = let replace '"' = "\\\""
replace c = [c]
in surround "\"" "\"" . concatMap replace
class GraphvizLabel a where
toGVItem :: a -> String
toGVLabel :: a -> String
toGVLabel = squareBrackets . ("label=" ++) . toGVItem
-- We only need to print Strings, Ints, Chars, and Maps.
instance GraphvizLabel String where
toGVItem = quoted
instance GraphvizLabel Int where
toGVItem = quoted . show
instance GraphvizLabel Char where
toGVItem = toGVItem . (: []) -- Custom behavior: no single quotes.
instance (GraphvizLabel k, GraphvizLabel v) => GraphvizLabel (Map k v) where
toGVItem = let kvfn k v = ((toGVItem k ++ "=" ++ toGVItem v) :)
in intercalate "," . M.foldWithKey kvfn []
toGVLabel = squareBrackets . toGVItem
In this setup, everything which we can output to Graphviz is an instance of GraphvizLabel
; the toGVItem
function quotes things, and toGVLabel
puts the whole thing in square brackets for immediate use. (I might have screwed some of the formatting you want up, but that part's just an example.) You then declare what's an instance of GraphvizLabel
, and how to turn it into an item. The TypeSynonymInstances
flag just lets us write instance GraphvizLabel String
instead of instance GraphvizLabel [Char]
; it's harmless.
Now, if you really need everything with a Show
instance to be an instance of GraphvizLabel
as well, there is a way. If you don't really need this, then don't use this code! If you do need to do this, you have to bring to bear the scarily-named UndecidableInstances
and OverlappingInstances
language extensions (and the less scarily named FlexibleInstances
). The reason for this is that you have to assert that everything which is Show
able is a GraphvizLabel
—but this is hard for the compiler to tell. For instance, if you use this code and write toGVLabel [1,2,3]
at the GHCi prompt, you'll get an error, since 1
has type Num a => a
, and Char
might be an instance of Num
! You have to explicitly specify toGVLabel ([1,2,3] :: [Int])
to get it to work. Again, this is probably unnecessarily heavy machinery to bring to bear on your problem. Instead, if you can limit the things you think will be converted to labels, which is very likely, you can just specify those things instead! But if you really want Show
ability to imply GraphvizLabel
ability, this is what you need:
{-# LANGUAGE TypeSynonymInstances, FlexibleInstances
, UndecidableInstances, OverlappingInstances #-}
-- Leave the module declaration, imports, formatting code, and class declaration
-- the same.
instance GraphvizLabel String where
toGVItem = quoted
instance Show a => GraphvizLabel a where
toGVItem = quoted . show
instance (GraphvizLabel k, GraphvizLabel v) => GraphvizLabel (Map k v) where
toGVItem = let kvfn k v = ((toGVItem k ++ "=" ++ toGVItem v) :)
in intercalate "," . M.foldWithKey kvfn []
toGVLabel = squareBrackets . toGVItem
Notice that your specific cases (GraphvizLabel String
and GraphvizLabel (Map k v)
) stay the same; you've just collapsed the Int
and Char
cases into the GraphvizLabel a
case. Remember, UndecidableInstances
means exactly what it says: the compiler cannot tell if instances are checkable or will instead make the typechecker loop! In this case, I am reasonably sure that everything here is in fact decidable (but if anybody notices where I'm wrong, please let me know). Nevertheless, using UndecidableInstances
should always be approached with caution.