> I would like to avoid using show all the time for printing strings e.g.
> 
> > val = "the sum of 2 and 2 is "++(show $ 2 + 2)++" whenever."
> 
> I would prefer to type something like:
> 
> > val = "the sum of 2 and 2 is "./(2+2)./" whenever." 
> > -- i can' find a better haskell compatible operator
> 
> I can't simply "show" the arguments of (./) because showing strings adds
> quotation marks which I don't want in this context.
> 
> So I tried creating my own Stringable class:
> > class Stringable a where
> >  toString::a -> String
> 
> > (./) :: (Stringable a,Stringable b)=> a->b->String
> > x./y = (toString x)++(toString y)

Nice idea. I polished the code somewhat ...

===============================================================================

> infixr 0 &

What about `&' for catenation?

> toString                      :: (Stringable a) => a -> String
> toString a                    =  toStrings a ""

> class (Show a) => Stringable a where
>     toStrings                 :: a -> ShowS
>     toStringList              :: [a] -> ShowS
>
>     toStrings                 =  shows
>     toStringList []           =  showString "[]"
>     toStringList (a : as)     =  showChar '[' . toStrings a . showl as
>         where showl []        =  showChar ']'
>               showl (a : as)  =  showString ", " . toStrings a . showl as

The class `Stringable' uses the `ShowS' mechanism to avoid quadratic
time behavior and employs the standard trick to allow overlapping
instances (Eric Meijer has written a short note about that topic):
[Char] and [a] should be treated differently.

> instance Stringable Char where
>     toStringList s            =  showString s

This instance declaration print strings as they are ...

> instance Stringable Int
>
> instance Stringable Integer
>
> instance Stringable a => Stringable [a]  where
>     toStrings                 =  toStringList
>
> instance Stringable ShowS where
>     toStrings                 =  id

This instance declaration is necessary to make `&' useable. Note that
this is not (Standard) Haskell but works only with Hugs 1.3c (and
probably with GHC's next release).

> (&)                           :: (Stringable a, Stringable b) => a -> b -> ShowS
> a & b                         =  toStrings a . toStrings b

Note that `&' yields `ShowS' and not `String'.

> val = "the sum of 2 and 2 is " & (2 + 2 :: Int) & " whenever."

Furthermore note that `val' has type `ShowS'. If quadratic time
behaviour is not a problem (does not occur?) you can safely omit the
`Stringable ShowS' instance and change `&' to `toString a ++ toString b'.

> render                        :: (Stringable a) => a -> IO ()
> render a                      =  putStr (toString a)

`render' is quite flexible:

? render val
the sum of 2 and 2 is 4 whenever.
? render (toString "aaa")
aaa
? render "aaa"
aaa
? render (toStrings "aaa")
aaa

===============================================================================

> Is there any way to convince Haskell to just resolve these numbers to
> SOMETHING by default?  Then I can just declare that type an instance of
> Stringable.

Unfortunately not. I did not succeed in persuading SPJ ;-). See

http://www.cs.chalmers.se/~rjmh/Haskell/Messages/Display.cgi?id=445

HTH, Ralf


Reply via email to