Function that can be called on Strings and Int. Ambiguous type variable problem - haskell

I want to write a function that can be called on numbers (e.g. 1) and on strings (e.g. "a"). It is important in my application to simplify "user code" as much as possible.
The minimal example of my code looks like this
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeSynonymInstances #-}
type StrInt = Either String Int
class Lift a where
toStrInt :: a -> StrInt
instance Lift String where
toStrInt= Left
instance Lift Int where
toStrInt= Right
declare:: StrInt ->String
declare (Left a) = "String: " ++ a
declare (Right n) = "Number: " ++ (show n)
declare' :: Lift a => a -> String
declare' a = declare (toStrInt a)
myDecA = declare' "a"
myDec1 = declare' 1
Compiling this gives the error
Ambiguous type variable ‘a0’ arising from a use of ‘declare'’
prevents the constraint ‘(Lift a0)’ from being solved.
I understand the problem and I know that I can replace the last line with any of the following:
myDec1 = declare' (1::Int)
myDec1 = declare (Right 1)
But that defeats the purpose of what I'm trying to achieve. Is there a clever way of setting the same idea such that it makes clear that 1 is an Int?
Also, In my application (more complex than the minimal example above) The declare function only works for Int s. So I can't generalize it for all Num a.

This is not possible using Haskell. The reason for this is that while 1 looks like an Int, it's actually a Num a => a. Haskell does not have a way to know that Int is the only a that satisfies (Num a, Lift a) => a, so it needs to be told this explicitly. For example, if I create in another module the following instance:
instance Num String where
...
Then declare' 1 becomes ambiguous, and could reasonably result in either "String:..." or "Int:...". Haskell can't know at compile time that I won't do this, so we have a problem.

Like I said in my comment, this is a hacky solution. There might be a cleaner way.
But what you can do is enable OverloadedStrings and then make NumStr an instance of IsString and Num so that you can convert literals to it.
{-# LANGUAGE OverloadedStrings #-}
module Hacky where
import Data.String (IsString(..))
newtype StrInt = StrInt (Either String Int)
instance IsString StrInt where
fromString str = StrInt (Left str)
instance Num StrInt where
-- fromIntegral is to convert 'Integer' to 'Int'.
fromInteger n = StrInt (Right (fromIntegral n))
-- other methods for 'Num' are missing...
declare :: StrInt -> String
declare (StrInt (Left a)) = "String: " ++ a
declare (StrInt (Right n)) = "Number: " ++ show n
main :: IO ()
main = do
putStrLn $ declare "hi"
putStrLn $ declare 1
Note that I didn't implement the other required methods for Num, which you may wish to do, otherwise code like declare (1 + 3) won't typecheck.
I'd be happier with this if there was something like OverloadedNumbers, but I couldn't find a pragma like that.

Related

Take action based on a type parameter's typeclass?

I suspect I have a fundamental misunderstanding to be corrected, so will start with the general concept and then zoom in on the particular instance that lead me to think this way.
Generally speaking, is it possible to write a function whose type signature has a parameterised type, and take different action depending on whether the type parameter belongs to a typeclass?
So for example if you had
data MyTree a = Node { val :: a, left :: Maybe (MyTree a), right :: Maybe (MyTree a) }
prettyPrint :: MyTree a -> String
prettyPrint (Show a => ...) t = show (val t)
prettyPrint t = show "?"
where prettyPrint $ Node 'x' Nothing Nothing would print x while prettyPrint $ Node id Nothing Nothing would print ?.
What lead me here is a few instances where I'm working on a complex, parameterised data type (eg. MyTree), which is progressing fine until I need to do some debugging. When I insert trace statements I find myself wishing my data type parameter derived Show when I use test (Showable) data. But I understand one should never add typeclass constraints in data declarations as the wonderfully enlightening LYAH puts it. That makes sense, I shouldn't have to artificially restrict my data type simply because I want to debug it.
So I end up adding the typeclass constraints to the code I'm debugging instead, but quickly discover they spread like a virus. Every function that calls the low level function I'm debugging also needs the constraint added, until I've basically just temporarily added the constraint to every function so I can get enough test coverage. Now my test code is polluting the code I'm trying to develop and steering it off course.
I thought it would be nice to pattern match instead and leave the constraint out of the signature, or use polymorphism and define debug versions of my function, or otherwise somehow wrap my debug traces in a conditional that only fires if the type parameter is an instance of Show. But in my meandering I couldn't find a way to do this or a sensible alternative.
A good mindset is that from the compiler's point of view, every type is potentially an instance of every class. When a type is not an instance of Show, it just means the instance has not been found yet, possibly not been written yet, but not that it doesn't exist.
Approach 1
...Therefore, trying to make a decision based on whether or not a type is an instance of a class is indeed quite fundamentally flawed. However, what you can do is to write a class that explicitly makes this distinction. For Show this could simply be
class MaybeShow a where
showIfPossible :: a -> Maybe a
A generalizable version is to wrap the following around the Show class:
{-# LANGUAGE GADTs #-}
data ShowDict a where
ShowDict :: Show a => ShowDict a
class MaybeShow a where
maybeShowDict :: Maybe (ShowDict a)
and then
{-# LANGUAGE TypeApplications, ScopedTypeVariables, UnicodeSyntax #-}
showIfPossible :: ∀ a . MaybeShow a => Maybe (a -> String)
showIfPossible = fmap (\ShowDict -> show) (maybeShowDict #a)
Either way, this would still mean you have the MaybeShow constraint polluting your codebase – which is in a sense better than Show as it doesn't preclude unshowable types, but in a sense also worse because it requires adding instance for all the types you need to use (even if they already have a Show instance).
Approach 2
You already seem to have considered adding the constraint to the data type instead. And although the old syntax data Show a => MyTree a = ... should indeed never be used, it is possible to encapsulate instances in data. In fact I already did it above with ShowDict. Rather than obtaining that implicitly via a MaybeShow constraint, you can also just add it optionally to your data type:
data MyTree a = Node { val :: a
, showable :: Maybe (ShowDict a)
, left :: Maybe (MyTree a)
, right :: Maybe (MyTree a) }
Of course, if all you're using the Show instance for is for showing the val of this specific node, then you could instead also just put the result right there:
data MyTree a = Node { val :: a
, valDescription :: Maybe (String)
, left :: Maybe (MyTree a)
, right :: Maybe (MyTree a) }
Now of course you're polluting your codebase in a different way: every function that generates a MyTree value needs to procure a Show instance, or decide it can't. This likely has less of an impact though, and especially not if MyTree is only an example and you have many more functions that just work on abstract containers instead.
Approach 3
At least for the specific case of debugging, but also some other use cases, it might be best use a separate means of turning the Show requirement on and off. The most brute-force way is a good old preprocessor flag:
{-# LANGUAGE CPP #-}
#define DEBUGMODE
-- (This could be controlled from your Cabal file)
prettyPrint ::
#ifdef DEBUGMODE
Show a =>
#endif
MyTree a -> String
#ifdef DEBUGMODE
prettyPrint (Show a => ...) t = show (val t)
#else
prettyPrint t = show "?"
#endif
A bit more refined is a constraint synonym and fitting debug function, that can be swapped out in just a single place:
{-# LANGUAGE ConstraintKinds #-}
#ifdef DEBUGMODE
type DebugShow a = Show a
debugShow :: DebugShow a => a -> String
debugShow = show
#else
type DebugShow a = ()
debugShow :: DebugShow a => a -> String
debugShow _ = "?"
#else
PrettyPrint :: DebugShow a => MyTree a -> String
PrettyPrint t = debugShow (val t)
The latter again pollutes the codebase with constraints, but you never need to write any new instances for these.
CPP is quite a blunt tool, in that it requires selecting globally during compilation whether or not you want to require Show. But it can also be done more confined, with a dedicated type-level flag:
{-# LANGUAGE TypeFamilies, DataKinds #-}
data DebugMode = NoDebug | DebugShowRequired
type family DebugShow mode a where
DebugShow 'NoDebug a = ()
DebugShow 'DebugShowRequired a = Show a
class KnownDebugMode (m :: DebugMode) where
debugShow :: DebugShow m a => a -> String
instance KnownDebugMode 'NoDebug where
debugShow _ = "?"
instance KnownDebugMode 'DebugShowRequired where
debugShow = show
{-# LANGUAGE AllowAmbiguousTypes #-}
prettyPrint :: ∀ m a . DebugShow m a => MyTree a -> String
prettyPrint t = debugShow (val t)
This looks a lot like approach 1, but the nice thing is that you don't need any new instances for individual a types.
The way to use prettyPrint now is to specify the debug mode with a type application. For example you could extract debug- and production-specific versions thus:
prettyPrintDebug :: Show a => MyTree a -> String
prettyPrintDebug = prettyPrint #('DebugShowRequired)
prettyPrintProduction :: MyTree a -> String
prettyPrintProduction = prettyPrint #('NoDebug)
I think the simplest approach is to explicitly define overlapping instances for the unshowable types you want. As #leftaroundabout pointed out this solution forces you to define instances for potencially many many types, for example a -> b, IO a, State s a, Maybe (a -> b), etc...
I am assuming that you mostly want to show a tree of type MyTree (a -> b). If that's the case this might do the trick
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE FlexibleInstances #-}
data MyTree a =
Node { val :: a
, left :: Maybe (MyTree a)
, right :: Maybe (MyTree a)
} deriving (Show, Functor) -- The functor instance is just a easy way to map every val to "?", but is not strictly necessary for this problem
-- Create a class for pretty printing. The is a package which already provides it
class Pretty a where
prettyprint :: a -> String
-- Define an instance when the inner type is showable. (here is simply show, but that's up to you)
instance Show a => Pretty (MyTree a) where
prettyprint = show
-- Define an instance for the function type.
-- Notice that this isn't an instance for "non-showable" types,
-- but only for the function type.
-- The overlapping is necessary to distinguish from the previous instance
instance {-# OVERLAPPING #-} Pretty (MyTree (a -> b)) where
prettyprint = show . fmap (const "?")
main = do
putStrLn
$ prettyprint
$ Node (1 :: Int)
(Just $ Node 2 Nothing Nothing)
Nothing
putStrLn
$ prettyprint
$ Node id
(Just $ Node (+ 1) Nothing Nothing)
Nothing
-- outputs
> Node {val = 1, left = Just (Node {val = 2, left = Nothing, right = Nothing}), right = Nothing}
> Node {val = "?", left = Just (Node {val = "?", left = Nothing, right = Nothing}), right = Nothing}
See the plugin if-instance: https://www.reddit.com/r/haskell/comments/x9k5fl/branching_on_constraints_ifinstance_applications/
{-# Options_GHC -fplugin=IfSat.Plugin #-}
import Data.Constraint.If (IfSat, ifSat)
prettyPrint :: IfSat (Show a) => a -> String
prettyPrint x = ifSat #(Show a) (show x) "?"
This is rarely what you want and if used incorrectly can be used to write unsafeCoerce, but this plugin is a recent development and it's good to keep in your back pocket. Previous solutions required a lot more boilerplate.
OP here. The other answers resoundingly answer the question I asked. After quite some time digesting them and experimenting, I've arrived at a particular solution to my particular fundamental goal, which satisfies me.
It certainly not general or sophisticated. But for me it's a great workaround, so I wanted to leave some breadcrumbs for others:
First I use the CPP trick to define two different trace wrappers, so I don't need to use show in the non-debug code:
{-# LANGUAGE CPP #-}
#define DEBUG
#ifdef DEBUG
import Debug.Trace ( trace )
type Traceable = Char
dTrace :: (Show a) => a -> b -> b
dTrace traceable expr = trace (show traceable) expr
#else
dTrace :: a -> b -> b
dTrace _ expr = expr
#endif
Similarly, I then define two different data types. Both are deriving (Show) but only the debug version actually results in something that will satisfy show.
data MyTree a = Node {
#ifdef DEBUG
val :: Traceable
#else
val :: a
#endif
, left :: Maybe (MyTree a)
, right :: Maybe (MyTree a)
} deriving (Show)
And that's it, the pollution stops there. Everything is controlled by the DEBUG define and the rest of the code remains unperturbed:
workOnTree :: MyTree a -> MyTree a
workOnTree t = dTrace t $ t{left=Just t}
go = workOnTree $ Node 'x' Nothing Nothing
main :: IO ()
main = putStrLn [val go]
If I combine the three code sections and compile with #define DEBUG, it outputs:
Node {val = 'x', left = Nothing, right = Nothing}
x
And with #define DEBUG commented out (and no other changes!), I get:
x
and Node will happily accept non-showable values for val.
Even without the CPP stuff (which, even as a long time fan of the C preprocessor, I can understand is not to all tastes), this is pretty manageable. At the least you could just manually swap a few lines to switch between testing and production.

Checking constraints at runtime

I'm trying to define a function that detects whether the type of an input satisfies a given constraint:
satisfies :: (c a => a -> b) -> a -> Maybe b
-- or the more general
claim :: (c => a) -> Maybe a
So the desired behaviour would be:
>>> :t satisfies #Show show
satisfies #Show show :: a -> Maybe String
>>> satisfies #Show show (0 :: Int)
Just "0"
>>> satisfies #Show show (id :: Int -> Int)
Nothing
The goal is to make it easy to define fully polymorphic functions that take
advantage of specializations when possible:
showAny :: a -> String
showAny (satisfies #Show show -> Just str) = str
showAny (satisfies #Typeable showType -> Just str) = "_ :: " ++ str
showAny _ = "_"
As the easiest thing I could try, my first attempt tried using -fdefer-to-runtime
{-# OPTIONS_GHC -fdefer-type-errors -Wno-deferred-type-errors #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE RankNTypes #-}
module Claim where
import System.IO.Unsafe (unsafePerformIO)
import System.IO.Error (catchIOError)
satisfies :: (c a => a -> b) -> a -> Maybe b
satisfies f a = unsafePerformIO $
(return . Just $! f a) `catchIOError` \_ -> return Nothing
This failed because -fdefer-type-errors doesn't defer the checking to
runtime, or allow further checking to be done in the context which it is
actually used (as I had hoped), but instead at compile time replaces found
type errors with the equivalent of error "MESSAGE".
Now I'm out of ideas. Is implementing satisfies even possible?
You can't dispatch on instance availability at runtime. Remember, a constraint is translated by the compiler into a type class dictionary - a record of functions that is passed around explicitly and accessed explicitly at runtime. The "fat arrow" => is represented at runtime by a "thin arrow" ->, so the elaborator needs to know at compile time which dictionary to pass around.
That is, the following crude example:
class Show a where
show :: a -> String
instance Show String where
show = id
showTwice :: Show a => a -> String
showTwice x = show x ++ show x
main = putStrLn $ showTwice "foo"
generates Core code which looks approximately like:
data Show_ a = Show_ { show :: a -> String }
showString_ :: Show_ String
showString_ = Show_ { show = id }
showTwice :: Show_ a -> a -> String
showTwice show_ x = show show_ x ++ show show_ x
main = putStrLn $ showTwice showString_ "foo"
When generating code for main, the compiler needs to know where to find showString_.
You can imagine a system wherein you can look up a type class dictionary at runtime with some sort of introspection mechanism, but this would produce weird behaviour from a language design perspective. The problem is orphan instances. If I write a function which attempts to look up a given instance in module A, and define such an instance in an unrelated module B, then the behaviour of that function when called from some client module C depends on whether B was imported by some other part of the program. Pretty strange!
A more usual way of doing "fully polymorphic functions that take advantage of specializations when possible" would be to put the function in question into a type class itself and give it a default implementation (perhaps with a default signature if the default implementation depends on some superclass). Your showAny would then look like this:
{-# LANGUAGE DefaultSignatures #-}
import Data.Typeable
class ShowAny a where
showAny :: a -> String
default showAny :: Typeable a => a -> String
showAny x = "_ :: " ++ show (typeOf x)
You'd need to implement ShowAny for all of the types with which you want to use showAny, but that's usually a single line of code,
instance (Typeable a, Typeable b) => ShowAny (a -> b)
and you can specialise an implementation for a given type just by overriding showAny.
instance ShowAny String where
showAny = id
You see this approach quite frequently in libraries which do generic programming. aeson, for example, can use GHC.Generics to serialise a given type to and from JSON (all you have to do is derive Generic and write two lines instance ToJSON MyType; instance FromJSON MyType), but you can also write your own instances of ToJSON and FromJSON if the generic code isn't fast enough or you need to customise the output.
An alternate workaround to the accepted answer is to pass the dictionaries around manually.
That is, given:
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeOperators #-}
module Claim where
data Proof c where QED :: c => Proof c
type Claim c = Maybe (Proof c)
type c ? a = Maybe (Proof (c a))
One can write:
showAny :: (Show? a, Typeable? a) -> a -> String
showAny (Just QED, _) a = show a
showAny (_, Just QED) a = "_ :: " ++ showType a
showAny _ _ = "_"
Which works accepably well:
>>> showAny (Nothing, Just QED) (id :: Int -> Int)
"_ :: Int -> Int"
>>> showAny (Just QED, Just QED) (0 :: Int)
"0"
>>> showAny (Nothing, Nothing) undefined
"_"

How can I read the metadata of a type at runtime?

I'd like to write a program that prints out some metadata of a Haskell type. Although I know this isn't valid code, the idea is something like:
data Person = Person { name :: String, age :: Int }
metadata :: Type -> String
metadata t = ???
metadata Person -- returns "Person (name,age)"
The important restriction being I don't have an instance of Person, just the type.
I've started looking into Generics & Typeable/Data, but without an instance I'm not sure they'll do what I need. Can anyone point me in the right direction?
Reflection in Haskell works using the Typeable class, which is defined in Data.Typeable and includes the typeOf* method to get a run-time representation of a value's type.
ghci> :m +Data.Typeable
ghci> :t typeOf 'a'
typeOf 'a' :: TypeRep
ghci> typeOf 'a' -- We could use any value of type Char and get the same result
Char -- the `Show` instance of `TypeRep` just returns the name of the type
If you want Typeable to work for your own types, you can have the compiler generate an instance for you with the DeriveDataTypeable extension.
{-# LANGUAGE DeriveDataTypeable #-}
import Data.Typeable
data Person = Person { name :: String, age :: Int } deriving Typeable
You can also write your own instance, but really, no one has the time for that. Apparently you can't - see the comments
You can now use typeOf to grab a run-time representation of your type. We can query information about the type constructor (abbreviated to TyCon) and its type arguments:
-- (undefined :: Person) stands for "some value of type Person".
-- If you have a real Person you can use that too.
-- typeOf does not use the value, only the type
-- (which is known at compile-time; typeOf is dispatched using the normal instance selection rules)
ghci> typeOf (undefined :: Person)
Person
ghci> tyConName $ typeRepTyCon $ typeOf (undefined :: Person)
"Person"
ghci> tyConModule $ typeRepTyCon $ typeOf (undefined :: Person)
"Main"
Data.Typeable also provides a type-safe cast operation which allows you to branch on a value's runtime type, somewhat like C#'s as operator.
f :: Typeable a => a -> String
f x = case (cast x :: Maybe Int) of
Just i -> "I can treat i as an int in this branch " ++ show (i * i)
Nothing -> case (cast x :: Maybe Bool) of
Just b -> "I can treat b as a bool in this branch " ++ if b then "yes" else "no"
Nothing -> "x was of some type other than Int or Bool"
ghci> f True
"I can treat b as a bool in this branch yes"
ghci> f (3 :: Int)
"I can treat i as an int in this branch 9"
Incidentally, a nicer way to write f is to use a GADT enumerating the set of types you expect your function to be called with. This allows us to lose the Maybe (f can never fail!), does a better job of documenting our assumptions, and gives compile-time feedback when we need to change the set of admissible argument types for f. (You can write a class to make Admissible implicit if you like.)
data Admissible a where
AdInt :: Admissible Int
AdBool :: Admissible Bool
f :: Admissible a -> a -> String
f AdInt i = "I can treat i as an int in this branch " ++ show (i * i)
f AdBool b = "I can treat b as a bool in this branch " ++ if b then "yes" else "no"
In reality I probably wouldn't do either of these - I'd just stick f in a class and define instances for Int and Bool.
If you want run-time information about the right-hand side of a type definition, you need to use the entertainingly-named Data.Data, which defines a subclass of Typeable called Data.** GHC can derive Data for you too, with the same extension:
{-# LANGUAGE DeriveDataTypeable #-}
import Data.Typeable
import Data.Data
data Person = Person { name :: String, age :: Int } deriving (Typeable, Data)
Now we can grab a run-time representation of the values of a type, not just the type itself:
ghci> dataTypeOf (undefined :: Person)
DataType {tycon = "Main.Person", datarep = AlgRep [Person]}
ghci> dataTypeConstrs $ dataTypeOf (undefined :: Person)
[Person] -- Person only defines one constructor, called Person
ghci> constrFields $ head $ dataTypeConstrs $ dataTypeOf (undefined :: Person)
["name","age"]
Data.Data is the API for generic programming; if you ever hear people talking about "Scrap Your Boilerplate", this (along with Data.Generics, which builds on Data.Data) is what they mean. For example, you can write a function which converts record types to JSON using reflection on the type's fields.
toJSON :: Data a => a -> String
-- Implementation omitted because it is boring.
-- But you only have to write the boring code once,
-- and it'll be able to serialise any instance of `Data`.
-- It's a good exercise to try to write this function yourself!
* In recent versions of GHC, this API has changed somewhat. Consult the docs.
** Yes, the fully-qualified name of that class is Data.Data.Data.

Binary instance for an existential

Given an existential data type, for example:
data Foo = forall a . (Typeable a, Binary a) => Foo a
I'd like to write instance Binary Foo. I can write the serialisation (serialise the TypeRep then serialise the value), but I can't figure out how to write the deserialisation. The basic problem is that given a TypeRep you need to map back to the type dictionary for that type - and I don't know if that can be done.
This question has been asked before on the haskell mailing list http://www.haskell.org/pipermail/haskell/2006-September/018522.html, but no answers were given.
You need some way that each Binary instance can register itself (just as in your witness version). You can do this by bundling each instance declaration with an exported foreign symbol, where the symbol name is derived from the TypeRep. Then when you want to deserialize you get the name from the TypeRep and look up that symbol dynamically (with dlsym() or something similar). The value exported by the foreign export can, e.g., be the deserializer function.
It's crazy ugly, but it works.
This can be solved in GHC 7.10 and onwards using the Static Pointers Language extension:
{-# LANGUAGE StaticPointers #-}
{-# LANGUAGE InstanceSigs #-}
data Foo = forall a . (StaticFoo a, Binary a, Show a) => Foo a
class StaticFoo a where
staticFoo :: a -> StaticPtr (Get Foo)
instance StaticFoo String where
staticFoo _ = static (Foo <$> (get :: Get String))
instance Binary Foo where
put (Foo x) = do
put $ staticKey $ staticFoo x
put x
get = do
ptr <- get
case unsafePerformIO (unsafeLookupStaticPtr ptr) of
Just value -> deRefStaticPtr value :: Get Foo
Nothing -> error "Binary Foo: unknown static pointer"
A full description of the solution can be found on this blog post, and a complete snippet here.
If you could do that, you would also be able to implement:
isValidRead :: TypeRep -> String -> Bool
This would be a function that changes its behavior due to someone defining a new type! Not very pure-ish.. I think (and hope) that one can't implement this in Haskell..
I have an answer that slightly works in some situations (not enough for my purposes), but may be the best that can be done. You can add a witness function to witness any types that you have, and then the deserialisation can lookup in the witness table. The rough idea is (untested):
witnesses :: IORef [Foo]
witnesses = unsafePerformIO $ newIORef []
witness :: (Typeable a, Binary a) => a -> IO ()
witness x = modifyIORef (Foo x :)
instance Binary Foo where
put (Foo x) = put (typeOf x) >> put x
get = do
ty <- get
wits <- unsafePerformIO $ readIORef witnesses
case [Foo x | Foo x <- wits, typeOf x == ty] of
Foo x:_ -> fmap Foo $ get `asTypeOf` return x
[] -> error $ "Could not find a witness for the type: " ++ show ty
The idea is that as you go through, you call witness on values of every type that you may plausibly encounter when deserialising. When you deserialise you search this list. The obvious problem is that if you fail to call witness before deserialisation you get a crash.

Haskell: variant of `show` that doesn't wrap String and Char in quotes

I'd like a variant of show (let's call it label) that acts just like show, except that it doesn't wrap Strings in " " or Chars in ' '. Examples:
> label 5
"5"
> label "hello"
"hello"
> label 'c'
"c"
I tried implementing this manually, but I ran into some walls. Here is what I tried:
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
module Label where
class (Show a) => Label a where
label :: a -> String
instance Label [Char] where
label str = str
instance Label Char where
label c = [c]
-- Default case
instance Show a => Label a where
label x = show x
However, because the default case's class overlaps instance Label [Char] and instance Label Char, those types don't work with the label function.
Is there a library function that provides this functionality? If not, is there a workaround to get the above code to work?
The code above isn't going to work because instances are chosen only based on the "head", that is, the part after the class name. The "context", the stuff before the => such as `Show a' is only examined afterwards. The context can eliminate an instance and produce a compiler error, but not cause the compiler to pick a different instance. Because of this behavior, overlapping instances are a potential ambiguity.
There are compiler extensions that can let you write more complicated instances, but I suspect you're probably best off just writing individual instances of your Label class. What purpose do you have in mind for this? Depending on what you're trying to accomplish, there might be something more special-purpose already out there.
Your example code is pretty simple, though--if you want, simply adding the OverlappingInstances extension should make it work with no further modifications. Using OverlappingInstances causes GHC to tolerate some ambiguity, so long as there's an obvious "most specific" instance. In your code, the two instances with concrete types are as specific as it gets, so there shouldn't be any problems.
Might as well add TypeSynonymInstances while you're at it, for better readability:
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverlappingInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE TypeSynonymInstances #-}
module Label where
class (Show a) => Label a where
label :: a -> String
instance Label String where label x = x
instance Label Char where label x = [x]
instance (Show a) => Label a where label = show
There's an OverlappingInstances language extension which will make this work.
Is there a library function that provides this functionality?
Yes. There's a fairly new library that provides helpful functions, such as toS, which can be used similarly to show. (see docs)
It can be installed with cabal under the string-conv package like so: cabal install string-conv
Reference:
Hackage
Not really what you want, since it adds an extra constraint to the type (Typeable)
but this is how you could do it generically:
Data.Generics> (show `extQ` (id :: String -> String) `extQ` ((:[]) :: Char -> String)) 1
"1"
Data.Generics> (show `extQ` (id :: String -> String) `extQ` ((:[]) :: Char -> String)) "hello"
"hello"
Data.Generics> (show `extQ` (id :: String -> String) `extQ` ((:[]) :: Char -> String)) 'c'
"c"
Data.Generics> (show `extQ` (id :: String -> String) `extQ` ((:[]) :: Char -> String)) ['f','l']
"fl"
Data.Generics> :t (show `extQ` (id :: String -> String) `extQ` ((:[]) :: Char -> String))
(show `extQ` (id :: String -> String) `extQ` ((:[]) :: Char -> String))
:: (Show a, Typeable a) => a -> String

Resources