| I would be more inclined to use <<.  The reason is typing efficiency.
| '&' is awkward to be typing frequently immediately after '"'.

I do not type that fast ;-).

| You are acutally using (.) below.  Is there a way to do that (via
| Fran like lifting?)?

I'm afraid no.

| > > 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).
| 
| Why does this instance declaration require 1.3c?  Also, are there
| substantive differences between Hugs 1.3c and GHC 3.3?  Are people
| prototyping w/ 1.3c and then planning to build with the next GHC?

Haskell requires that the instance head is of the form C a1 ... ak
where ai are type variables. However, the code _does_ work with GHC 3.2
if the flag `-fglasgow-exts' is on (sorry for the incomplete
information).

| > > (&)                               :: (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'.
| 
| I am not understanding this last bit.  Can you explain further?

Well. If you change (<<) to

> (<<)                          :: (Stringable a, Stringable b) => a -> b -> String
> a << b                        =  toString a ++ toString b

and make nested calls to (<<) you may experience quadratic time
behaviour. The standard example involves printing a tree:

> data Bush a                   =  Leaf a | Fork (Bush a) (Bush a)
>                                  deriving (Show)
>
> lay                           :: (Stringable a) => Bush a -> String
> lay (Leaf a)                  =  "(Leaf " << a << ")"
> lay (Fork l r)                =  "(Fork " << lay l << lay r << ")"

Simply try

        lay $ leftist [1 .. 10000 :: Int]

where leftist is defined as follows.

> leftist                       =  foldl1 Fork . map Leaf

BTW With the original definition of (<<) it is quite easy to make
`Bush' an instance of `Stringable'.

> instance (Stringable a) => Stringable (Bush a) where
>     toStrings (Leaf a)        =  "(Leaf " << a << ")"
>     toStrings (Fork l r)      =  "(Fork " << l << r << ")"

Maybe cunning, but I like it ;-).

Ralf


Reply via email to