[Haskell-cafe] Reducing code for efficient ShowS

Sean Leather leather at cs.uu.nl
Fri Sep 5 10:11:57 EDT 2008


It happens very often that I want to convert a number of values to strings
and
concatenate those strings into one. No surprise there, of course. Well, I'd
prefer to do it efficiently and with as little code as necessary.

> {-# LANGUAGE TypeSynonymInstances #-}
> module ShowsDemo where

Let's say I want to generate the string "(42 abc)" starting with a number
and a
string stored in variables.

> n = 42 :: Int
> s = "abc"

What are my options?

There's the obvious approach that's described in every tutorial, book, and
research paper (for didactic purposes, of course).

> ex1 = "(" ++ show n ++ " " ++ s ++ ")"

It's pretty concise, but it's horribly inefficient due to the use of (++).

Then, there's the ShowS approach.

> ex2 = showChar '(' . shows n . showChar ' ' . showString s . showChar ')'
$ ""

This is more efficient, but now the code has bloated up a lot.

Why can't I have my cake and eat it, too? I want to write with as little
code as
|ex1| (or less if possible), and I want it to be as efficient as |ex2|.

I propose this example as an improvement.

> ex3 = '(' .+. n .+. ' ' .+. s .$. ')'

It uses a class I'm calling |Shows|. The class has one method that simply
converts a value to the type |ShowS|, where |ShowS| is a type synonym for
|String -> String| and is defined in the Prelude.

> class Shows a where
>   toShows :: a -> ShowS

Notice the lack of context involving the |Show| class. That's important,
because
it allows us to create more instances than we could if we were restricted by
|(Show a) => ...|, esp. the |ShowS| instance below.

The instances for types are all very simple. Most will appear like the
instance
for |Int|.

> instance Shows Int where
>   toShows = shows

Since we don't have |Show| in the class context above, we can't make this a
default method.

We need a few special instances for |Char| and |String| to make these types
convenient to use in the expected way.

> instance Shows Char where
>   toShows = showChar

> instance Shows String where
>   toShows = showString

We also need an instance for |ShowS| in order to facilitate concatenation.

> instance Shows ShowS where
>   toShows = id

Now, we define a few operators that use |toShows| and make our lives easier
and
our code more concise.

The |(.+.)| replaces list appending, |(++)|, in |ex1| and function
composition,
|.|, in |ex2|.

> infixl 5 .+.
> (.+.) :: (Shows a, Shows b) => a -> b -> ShowS
> a .+. b = toShows a . toShows b

The |(.$.)| replaces the need for |($)| in |ex2|.

> infixl 4 .$.
> (.$.) :: (Shows a, Shows b) => a -> b -> String
> a .$. b = (a .+. b) ""

I would find something like this very useful. I'm guessing the idea can be
applied to |ByteString| as well. Does it exist in some other form?

Sean
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20080905/f6f79311/attachment.htm


More information about the Haskell-Cafe mailing list