How to specialize (overload) behavior of a function for a single type? [duplicate] - haskell

This question already has answers here:
How to convert arbitrary type to string, without adding extra quotes to strings?
(3 answers)
Closed 2 years ago.
I'm working through Real World Haskell, and as part of an exercise realized I wanted a function similar to show :: Show(a) => a -> String, but which leaves Strings untouched (rather than escaping quotes). In pseudocode, what I want is:
show' :: String -> String
show' = id
show':: Show(a) => a -> String
show' = show
Obviously this doesn't work (ghc complains of multiple type signatures and multiple declarations). It seems like I should use typeclasses instead. When I try to write this, the compiler keeps suggesting I add more more language extensions:
{-# LANGUAGE FlexibleInstances, UndecidableInstances, IncoherentInstances #-}
class Show' a where
show' :: a -> String
instance Show' String where
show' = id
instance (Show a) => Show' a where
show' = show
-- x == "abc"
x = show' "abc"
y = show' 9
At first this seems to work: x == "abc" and y == "9" as expected. But when I try to use this in another polymorphic function, the compiler seems to always resolve it to the general implementation:
use :: (Show a) => a -> String
use x = show' x
-- z == "\"abc\""
z = use "abc"
So I'm doing something wrong here, and I wonder if there is a way to do this without a bunch of language extensions (some of these don't seem like things I ought to use recklessly). How can I define this show' using the existing show function?

From a comment of the OP:
[I] was surprised that such a simple function to describe was so difficult to implement.
That's no simple function at all, since it sort-of breaks the usual guarantees of typeclass-based polymorphism. When we see an instance
instance Show' a => Show' [a] where ...
we usually assume this instance to be taken for all list types, with no exceptions. Universal quantification over types a really means forall a.
Overlapping / incoherent instances break this assumption, and allow "special cases" like yours, as David pointed out in his answer. That's one possible solution, but note that by breaking the assumption above, overlapping / incoherent instances make instance resolution rather fragile, sometimes leading to the wrong instance being taken, unexpectedly.
As an alternative, you can consider exploiting the Typeable typeclass which I believe is less controversial:
import Data.Typeable
show' :: (Show a, Typeable a) => a -> String
show' x = case cast x of
Just s -> s -- cast succeeded, it is a string
Nothing -> show x -- case failed, it is not a string
Note that the presence of Typeable makes it evident, in the type, that this function is defined using ad-hoc polymorphism, allowing us to check whether a is such and such type, which is normally impossible under parametric polymorphism.
Note that this does not require IncoherentInstances nor OverlappingInstances.

The only thing use knows about the type of its argument is that it's an instance of Show. Since this is all it knows, it must use the "general" instance which only requires Show.
What you really want, instead of that, is to tell it that it can be any instance of Show' (rather than any instance of Show). A small change fixes this:
use :: (Show' a) => a -> String
An aside: If I remember correctly, IncoherentInstances can occasionally cause some issues. I think it is ok here, but this is something to keep in mind if you are creating more instances in the same file that has that extension enabled.
UndecidableInstances can potentially cause the type checker (and hence the compiler as a whole) to go into an infinite loop, if there is a cycle in dependencies between instances of a type class. That isn't the case here, but it's worth mentioning.
To answer your other question: It is not possible to do this specific thing without using these language extensions. Is there more context to this problem (details you've left out, etc)? Maybe there is a better way to approach the larger problem.

Related

Haskell: Define Show function for a user defined type, which is defined by "type" key word

Let's say I have the type StrInt defined as below
type StrInt = (String, Int)
toStrInt:: Str -> Int -> StrInt
toStrInt str int = (str, int)
I want the Show function to work as below:
Input: show (toStrInt "Hello", 123)
Output: "Hello123"
I have tried to define show as below:
instance Show StrInt where
show (str, int) = (show str) ++ (show int)
But that gives me error:
Illegal instance declaration for ‘Show StrInt’
(All instance types must be of the form (T t1 ... tn)
where T is not a synonym.
Use TypeSynonymInstances if you want to disable this.)
In the instance declaration for ‘Show StrInt’
Any ideas on how to solve this issue?
Appreciate your help!
What you're trying to do is 1. not a good idea to start with, 2. conflicts with the already-existing Show instance and is therefore not possible without OverlappingInstances hackery (which is almost never a good idea), and 3. the error message you're getting is not related to these problems; other class-instances with the same message may be perfectly fine but of course require the extension that GHC asks about.
The Show class is not for generating arbitrary string output in whatever format you feel looks nice right now. That's the purpose of pretty-printing. Show instead is supposed to yield syntactically valid Haskell, like the standard instance does:
Prelude> putStrLn $ show (("Hello,"++" World!", 7+3) :: (String,Int))
("Hello, World!",10)
Prelude> ("Hello, World!",10) -- pasted back the previous output
("Hello, World!",10)
If you write any Show instance yourself, it should also have this property.
Again because (String, Int) already has a Show instance, albeit just one arising from more generic instances namely
instance (Show a, Show b) => Show (a,b)
instance Show a => Show [a]
instance Show Int
declaring a new instance for the same type results in a conflict. Technically speaking this could be circumvented by using an {-# OVERLAPPING #-} pragma, but I would strongly advise against this because doing that kind of thing can lead to very confusing behaviour down the line when instance resolution inexplicably changes based on how the types are presented.
Instead, when you really have a good reason to give two different instances to a type containing given data, the right thing to do is generally to make it a separate type (so it's clear that there will be different behaviour) which just happens to have the same components.
data StrInt' = StrInt String Int
instance Show StrInt' where
...
That actually compiles without any further issues or need for extensions. (Alternatively you can also use newtype StrInt = StrInt (String, Int), but that doesn't really buy you anything and just means you can't bring in record labels.)
Instances of the form instance ClassName TypeSynonym are possible too, and can sometimes make sense, but as GHC already informed you they require the TypeSynonymInstances extension or one that supersedes it. In fact TypeSynonymInstances is not enough if the synonym points to a composite type like a tuple, in that case you need FlexibleInstances (which includes TypeSynonymInstances), an extension I enable all of the time.
{-# LANGUAGE FlexibleInstances #-}
class C
type StrInt = (String, Int)
instance C StrInt

How to declare instances of a typeclass (like Show) for all types in my own typeclass?

I have a typeclass:
class Wrapper w where
open :: w -> Map String Int
close :: Map String Int -> w
It doesn't look very useful, but I use it to strongly (not just a type synonym) distinguish between semantically different varieties of Map String Ints:
newtype FlapMap = Flap (Map String Int)
newtype SnapMap = Snap (Map String Int)
...
and still have functions that operate on any type of the class.
Is there a better way to do this distinction (maybe without the Wrapper instances boilerplate)?
I want to do this:
instance (Wrapper wrapper) => Show wrapper where
show w = show $ toList $ open w
instead of writing many boilerplate Show instances as well.
Via FlexibleInstances and UndecidableInstances, GHC leads me to a point where it thinks my instance declaration applies to everything, as it allegedly clashes with the other Show instances in my code and in GHC.Show. HaskellWiki and StackOverflow answerers and HaskellWiki convince me OverlappingInstances is not quite safe and possibly confusing. GHC doesn't even suggest it.
Why does GHC first complain about not knowing which instance of fx Show Int to pick (so why it doesn't look at the constraint I give at compile time?) and then, being told that instances may overlap, suddenly know what to do?
Can I avoid allowing OverlappingInstances with my newtypes?
You can’t do this without OverlappingInstances, which as you mention, is unpredictable. It won’t help you here, anyway, so you pretty much can’t do this at all without a wrapper type.
That’s rather unsatisfying, of course, so why is this the case? As you’ve already determined, GHC does not look at the instance context when picking an instance, only the instance head. Why? Well, consider the following code:
class Foo a where
fooToString :: a -> String
class Bar a where
barToString :: a -> String
data Something = Something
instance Foo Something where
fooToString _ = "foo something"
instance Bar Something where
barToString _ = "bar something"
instance Foo a => Show a where
show = fooToString
instance Bar a => Show a where
show = barToString
If you consider the Foo or Bar typeclasses in isolation, the above definitions make sense. Anything that implements the Foo typeclass should get a Show instance “for free”. Unfortunately, the same is true of the Bar instance, so now you have two valid instances for show Something.
Since typeclasses are always open (and indeed, Show must be open if you are able to define your own instances for it), it’s impossible to know that someone will not come along and add their own similar instance, then create an instance on your datatype, creating ambiguity. This is effectively the classic diamond problem from OO multiple inheritance in typeclass form.
The best you can get is to create a wrapper type that provides the relevant instances:
{-# LANGUAGE ExistentialQuantification #-}
data ShowableWrapper = forall w. Wrapper w => ShowableWrapper w
instance Show ShowableWrapper where
show (ShowableWrapper w) = show . toList $ open w
At that point, though, you really aren’t getting much of an advantage over just writing your own showWrapper :: Wrapper w => w -> String function.

Haskell: Filtering by type

For any particular type A:
data A = A Int
is is possible to write this function?
filterByType :: a -> Maybe a
It should return Just . id if value of type A is given, and Nothing for value of any other types.
Using any means (GHC exts, TH, introspection, etc.)
NB. Since my last question about Haskell typesystem was criticized by the community as "terribly oversimplified", I feel the need to state, that this is a purely academic interest in Haskell typesystem limitations, without any particular task behind it that needs to be solved.
You are looking for cast at Data.Typeable
cast :: forall a b. (Typeable a, Typeable b) => a -> Maybe b
Related question here
Example
{-# LANGUAGE DeriveDataTypeable #-}
import Data.Typeable
data A = A Int deriving (Show, Typeable)
data B = B String deriving (Show, Typeable)
showByType :: Typeable a =>a ->String
showByType x = case (cast x, cast x) of
(Just (A y), _) ->"Type A: " ++ show y
(_, Just (B z)) ->"Type B: " ++ show z
then
> putStrLn $ showByType $ A 4
Type A: 4
> putStrLn $ showByType $ B "Peter"
Type B: "Peter"
>
Without Typeable derivation, no information exists about the underlying type, you can anyway perform some cast transformation like
import Unsafe.Coerce (unsafeCoerce)
filterByType :: a -> Maybe a
filterByType x = if SOMECHECK then Just (unsafeCoerce x) else Nothing
but, where is that information?
Then, you cannot write your function (or I don't know how) but in some context (binary memory inspection, template haskell, ...) may be.
No, you can't write this function. In Haskell, values without type class constraints are parametric in their type variables. This means we know that they have to behave exactly the same when instantiated at any particular type¹; in particular, and relevant to your question, this means they cannot inspect their type parameters.
This design means that that all types can be erased at run time, which GHC does in fact do. So even stepping outside of Haskell qua Haskell, unsafe tricks won't be able to help you, as the runtime representation is sort of parametric, too.
If you want something like this, josejuan's suggestion of using Typeable's cast operation is a good one.
¹ Modulo some details with seq.
A function of type a -> Maybe a is trivial. It's just Just. A function filterByType :: a -> Maybe b is impossible.
This is because once you've compiled your program, a and b are gone. There is no run time type information in Haskell, at all.
However, as mentioned in another answer you can write a function:
cast :: (Typeable a, Typeable b) => a -> Maybe b
The reason you can write this is because the constraint Typeable a tells the compiler to, where ever this function is called, pass along a run-time dictionary of values specified by Typeable. These are useful operations that can build up and tear down a great range of Haskell types. The compiler is incredibly smart about this and can pass in the right dictionary for virtually any type you use the function on.
Without this run-time dictionary, however, you cannot do anything. Without a constraint of Typeable, you simply do not get the run-time dictionary.
All that aside, if you don't mind my asking, what exactly do you want this function for? Filtering by a type is not actually useful in Haskell, so if you're trying to do that, you're probably trying to solve something the wrong way.

Why can't I use the type `Show a => [Something -> a]`?

I have a record type say
data Rec {
recNumber :: Int
, recName :: String
-- more fields of various types
}
And I want to write a toString function for Rec :
recToString :: Rec -> String
recToString r = intercalate "\t" $ map ($ r) fields
where fields = [show . recNumber, show . recName]
This works. fields has type [Rec -> String]. But I'm lazy and I would prefer writing
recToString r = intercalate "\t" $ map (\f -> show $ f r) fields
where fields = [recNumber, recName]
But this doesn't work. Intuitively I would say fields has type Show a => [Rec -> a] and this should be ok. But Haskell doesn't allow it.
I'd like to understand what is going on here. Would I be right if I said that in the first case I get a list of functions such that the 2 instances of show are actually not the same function, but Haskell is able to determine which is which at compile time (which is why it's ok).
[show . recNumber, show . recName]
^-- This is show in instance Show Number
^-- This is show in instance Show String
Whereas in the second case, I only have one literal use of show in the code, and that would have to refer to multiple instances, not determined at compile time ?
map (\f -> show $ f r) fields
^-- Must be both instances at the same time
Can someone help me understand this ? And also are there workarounds or type system expansions that allow this ?
The type signature doesn't say what you think it says.
This seems to be a common misunderstanding. Consider the function
foo :: Show a => Rec -> a
People frequently seem to think this means that "foo can return any type that it wants to, so long as that type supports Show". It doesn't.
What it actually means is that foo must be able to return any possible type, because the caller gets to choose what the return type should be.
A few moments' thought will reveal that foo actually cannot exist. There is no way to turn a Rec into any possible type that can ever exist. It can't be done.
People often try to do something like Show a => [a] to mean "a list of mixed types but they all have Show". That obviously doesn't work; this type actually means that the list elements can be any type, but they still have to be all the same.
What you're trying to do seems reasonable enough. Unfortunately, I think your first example is about as close as you can get. You could try using tuples and lenses to get around this. You could try using Template Haskell instead. But unless you've got a hell of a lot of fields, it's probably not even worth the effort.
The type you actually want is not:
Show a => [Rec -> a]
Any type declaration with unbound type variables has an implicit forall. The above is equivalent to:
forall a. Show a => [Rec -> a]
This isn't what you wan't, because the a must be specialized to a single type for the entire list. (By the caller, to any one type they choose, as MathematicalOrchid points out.) Because you want the a of each element in the list to be able to be instantiated differently... what you are actually seeking is an existential type.
[exists a. Show a => Rec -> a]
You are wishing for a form of subtyping that Haskell does not support very well. The above syntax is not supported at all by GHC. You can use newtypes to sort of accomplish this:
{-# LANGUAGE ExistentialQuantification #-}
newtype Showy = forall a. Show a => Showy a
fields :: [Rec -> Showy]
fields = [Showy . recNumber, Showy . recName]
But unfortunatley, that is just as tedious as converting directly to strings, isn't it?
I don't believe that lens is capable of getting around this particular weakness of the Haskell type system:
recToString :: Rec -> String
recToString r = intercalate "\t" $ toListOf (each . to fieldShown) fields
where fields = (recNumber, recName)
fieldShown f = show (f r)
-- error: Couldn't match type Int with [Char]
Suppose the fields do have the same type:
fields = [recNumber, recNumber]
Then it works, and Haskell figures out which show function instance to use at compile time; it doesn't have to look it up dynamically.
If you manually write out show each time, as in your original example, then Haskell can determine the correct instance for each call to show at compile time.
As for existentials... it depends on implementation, but presumably, the compiler cannot determine which instance to use statically, so a dynamic lookup will be used instead.
I'd like to suggest something very simple instead:
recToString r = intercalate "\t" [s recNumber, s recName]
where s f = show (f r)
All the elements of a list in Haskell must have the same type, so a list containing one Int and one String simply cannot exist. It is possible to get around this in GHC using existential types, but you probably shouldn't (this use of existentials is widely considered an anti-pattern, and it doesn't tend to perform terribly well). Another option would be to switch from a list to a tuple, and use some weird stuff from the lens package to map over both parts. It might even work.

Best way to implement ad-hoc polymorphism in Haskell?

I have a polymorphic function like:
convert :: (Show a) => a -> String
convert = " [label=" ++ (show a) ++ "]"
But sometimes I want to pass it a Data.Map and do some more fancy key value conversion. I know I can't pattern match here because Data.Map is an abstract data type (according to this similar SO question), but I have been unsuccessful using guards to this end, and I'm not sure if ViewPatterns would help here (and would rather avoid them for portability).
This is more what I want:
import qualified Data.Map as M
convert :: (Show a) => a -> String
convert a
| M.size \=0 = processMap2FancyKVString a -- Heres a Data.Map
| otherwise = " [label=" ++ (show a) ++ "]" -- Probably a string
But this doesn't work because M.size can't take anything other than a Data.Map.
Specifically, I am trying to modify the sl utility function in the Functional Graph Library in order to handle coloring and other attributes of edges in GraphViz output.
Update
I wish I could accept all three answers by TomMD, Antal S-Z, and luqui to this question as they all understood what I really was asking. I would say:
Antal S-Z gave the most 'elegant' solution as applied to the FGL but would also require the most rewriting and rethinking to implement in personal problem.
TomMD gave a great answer that lies somewhere between Antal S-Z's and luqui's in terms of applicability vs. correctness. It also is direct and to the point which I appreciate greatly and why I chose his answer.
luqui gave the best 'get it working quickly' answer which I will probably be using in practice (as I'm a grad student, and this is just some throwaway code to test some ideas). The reason I didn't accept was because TomMD's answer will probably help other people in more general situations better.
With that said, they are all excellent answers and the above classification is a gross simplification. I've also updated the question title to better represent my question (Thanks Thanks again for broadening my horizons everyone!
What you just explained is you want a function that behaves differently based on the type of the input. While you could use a data wrapper, thus closing the function for all time:
data Convertable k a = ConvMap (Map k a) | ConvOther a
convert (ConvMap m) = ...
convert (ConvOther o) = ...
A better way is to use type classes, thus leaving the convert function open and extensible while preventing users from inputting non-sensical combinations (ex: ConvOther M.empty).
class (Show a) => Convertable a where
convert :: a -> String
instance Convertable (M.Map k a) where
convert m = processMap2FancyKVString m
newtype ConvWrapper a = CW a
instance Convertable (ConvWrapper a) where
convert (CW a) = " [label=" ++ (show a) ++ "]"
In this manner you can have the instances you want used for each different data type and every time a new specialization is needed you can extend the definition of convert simply by adding another instance Convertable NewDataType where ....
Some people might frown at the newtype wrapper and suggest an instance like:
instance Convertable a where
convert ...
But this will require the strongly discouraged overlapping and undecidable instances extensions for very little programmer convenience.
You may not be asking the right thing. I'm going to assume that you either have a graph whose nodes are all Maps or you have a graph whose nodes are all something else. If you need a graph where Maps and non-maps coexist, then there is more to your problem (but this solution will still help). See the end of my answer in that case.
The cleanest answer here is simply to use different convert functions for different types, and have any type that depends on convert take it as an argument (a higher order function).
So in GraphViz (avoiding redesigning this crappy code) I would modify the graphviz function to look like:
graphvizWithLabeler :: (a -> String) -> ... -> String
graphvizWithLabeler labeler ... =
...
where sa = labeler a
And then have graphviz trivially delegate to it:
graphviz = graphvizWithLabeler sl
Then graphviz continues to work as before, and you have graphvizWithLabeler when you need the more powerful version.
So for graphs whose nodes are Maps, use graphvizWithLabeler processMap2FancyKVString, otherwise use graphviz. This decision can be postponed as long as possible by taking relevant things as higher order functions or typeclass methods.
If you need to have Maps and other things coexisting in the same graph, then you need to find a single type inhabited by everything a node could be. This is similar to TomMD's suggestion. For example:
data NodeType
= MapNode (Map.Map Foo Bar)
| IntNode Int
Parameterized to the level of genericity you need, of course. Then your labeler function should decide what to do in each of those cases.
A key point to remember is that Haskell has no downcasting. A function of type foo :: a -> a has no way of knowing anything about what was passed to it (within reason, cool your jets pedants). So the function you were trying to write is impossible to express in Haskell. But as you can see, there are other ways to get the job done, and they turn out to be more modular.
Did that tell you what you needed to know to accomplish what you wanted?
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 Showable 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 Showable 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 Showability to imply GraphvizLabelability, 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.

Resources