开发者

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 -&g开发者_运维百科t; 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

0

上一篇:

下一篇:

精彩评论

暂无评论...
验证码 换一张
取 消

最新问答

问答排行榜