
A small stylistic question: what's the "best" way to build strings containing other values? For example, I have: data Process = Stop | Prefix String Process | External Process Process instance Show Process where show Stop = "Stop" show (Prefix l p) = "(" ++ l ++ "->" ++ show p ++ ")" show (External p q) = "(" ++ show p ++ " [] " ++ show q ++ ")" but to me the extensive use of ++ is not particularly readable. I'm very fond of Python's interpolation approach, where we'd have something like the following for the External case: def __str__(self): return "(%s [] %s)" % (self.p, self.q) which to me seems clearer, or at least easier to work out roughly what the string's going to look like. (The %s does an implicit "convert to string", btw). Is there a facility like this in Haskell? Or something else I should be using, other than lots of ++ ? Thanks, -Andy -- Andy Gimblett Computer Science Department University of Wales Swansea http://www.cs.swan.ac.uk/~csandy/

How about this? instance Show Process where show Stop = "Stop" show (Prefix l p) = concat ["(", l, "->", show p, ")"] show (External p q) = concat ["(", show p, " [] ", show q, ")"] Hope that helps, Bryn Andy Gimblett wrote:
A small stylistic question: what's the "best" way to build strings containing other values? For example, I have:
data Process = Stop | Prefix String Process | External Process Process
instance Show Process where show Stop = "Stop" show (Prefix l p) = "(" ++ l ++ "->" ++ show p ++ ")" show (External p q) = "(" ++ show p ++ " [] " ++ show q ++ ")"
but to me the extensive use of ++ is not particularly readable.
I'm very fond of Python's interpolation approach, where we'd have something like the following for the External case:
def __str__(self): return "(%s [] %s)" % (self.p, self.q)
which to me seems clearer, or at least easier to work out roughly what the string's going to look like. (The %s does an implicit "convert to string", btw).
Is there a facility like this in Haskell? Or something else I should be using, other than lots of ++ ?
Thanks,
-Andy

On 7/20/05, Andy Gimblett
A small stylistic question: what's the "best" way to build strings containing other values? For example, I have:
data Process = Stop | Prefix String Process | External Process Process
instance Show Process where show Stop = "Stop" show (Prefix l p) = "(" ++ l ++ "->" ++ show p ++ ")" show (External p q) = "(" ++ show p ++ " [] " ++ show q ++ ")"
How about leaving the Show instance automatically derived and defining this instead: showProcess :: Process -> ShowS showProcess Stop = showString "Stop" showProcess (Prefix l p) = showBody (showString l) (showProcess p) showProcess (External p q) = showBody (showProcess p) (showProcess q) showBody :: ShowS -> ShowS -> ShowS showBody a b = showParen True (a . showString " [] " . b)
but to me the extensive use of ++ is not particularly readable.
I'm very fond of Python's interpolation approach, where we'd have something like the following for the External case:
def __str__(self): return "(%s [] %s)" % (self.p, self.q)
which to me seems clearer, or at least easier to work out roughly what the string's going to look like. (The %s does an implicit "convert to string", btw).
Is there a facility like this in Haskell? Or something else I should be using, other than lots of ++ ?
There's Text.Printf: Prelude Text.Printf> printf "(%s [] %s)" "hello" "world" :: String "(hello [] world)" -- Friendly, Lemmih

On Wed, Jul 20, 2005 at 07:00:22PM +0200, Lemmih wrote:
On 7/20/05, Andy Gimblett
wrote: Is there a facility like this in Haskell? Or something else I should be using, other than lots of ++ ?
There's Text.Printf:
Prelude Text.Printf> printf "(%s [] %s)" "hello" "world" :: String "(hello [] world)"
If you only use GHC, you can also implement (or borrow) a type-safe printf using Template Haskell. I think there's some implementation made by Ian Lynagh. Recently I needed to build strings containing shell commands and I also didn't like the ++ approach. I didn't like the printf approach, but rather wanted something more like shell's or Perl's string interpolation, so I could write something like "($p [] $q)" and have $p and $q expanded to values of p and q. I created a small TH library for this (attached). It uses such syntax: $(interp "(%{p} [] %{q})"). I used % because I knew I would often have to use literal $'s. Unfortunately it has some problems. First, TH sometimes doesn't like when I use a global variable in %{ }. I had to work around it by defining additional local helper variables. Second, it would be nice to be able to put arbitrary Haskell expressions inside %{ } - but I couldn't find a Haskell syntax parser producing TH ASTs. There must be some - I guess Template Haskell uses one internally. Best regards Tomasz

On Wed, 2005-07-20 at 17:06 +0100, Andy Gimblett wrote:
A small stylistic question: what's the "best" way to build strings containing other values? For example, I have:
data Process = Stop | Prefix String Process | External Process Process
instance Show Process where show Stop = "Stop" show (Prefix l p) = "(" ++ l ++ "->" ++ show p ++ ")" show (External p q) = "(" ++ show p ++ " [] " ++ show q ++ ")"
but to me the extensive use of ++ is not particularly readable.
It is also inefficient because append has complexity proportional to the length of its left argument. That's why the Prelude defines: type ShowS = String -> String and functions like showsPrec, shows, showChar
Is there a facility like this in Haskell? Or something else I should be using, other than lots of ++ ?
It looks to me like you are doing some kind of pretty printing - that is you are not printing the term using Haskell syntax. My preference is to only use Show where it is derived from the data declaration, and use a hand-written pretty printer for other tasks, for example Text.PrettyPrint Cheers, Bernie.

On Thu, Jul 21, 2005 at 04:55:15PM +1000, Bernard Pope wrote:
On Wed, 2005-07-20 at 17:06 +0100, Andy Gimblett wrote:
show (Prefix l p) = "(" ++ l ++ "->" ++ show p ++ ")" show (External p q) = "(" ++ show p ++ " [] " ++ show q ++ ")"
but to me the extensive use of ++ is not particularly readable.
It is also inefficient because append has complexity proportional to the length of its left argument. That's why the Prelude defines:
type ShowS = String -> String
and functions like showsPrec, shows, showChar
It's not that bad in this case, because ++ is right-associative. Best regards Tomasz

On Thu, 2005-07-21 at 09:24 +0200, Tomasz Zielonka wrote:
On Thu, Jul 21, 2005 at 04:55:15PM +1000, Bernard Pope wrote:
On Wed, 2005-07-20 at 17:06 +0100, Andy Gimblett wrote:
show (Prefix l p) = "(" ++ l ++ "->" ++ show p ++ ")" show (External p q) = "(" ++ show p ++ " [] " ++ show q ++ ")"
but to me the extensive use of ++ is not particularly readable.
It is also inefficient because append has complexity proportional to the length of its left argument. That's why the Prelude defines:
type ShowS = String -> String
and functions like showsPrec, shows, showChar
It's not that bad in this case, because ++ is right-associative.
You are right, in this case it is not too bad. I meant that there are potential efficiency problems with this style of generating strings, which ShowS and the pretty printers address. Cheers, Bernie.

Andy Gimblett
show (External p q) = "(" ++ show p ++ " [] " ++ show q ++ ")"
but to me the extensive use of ++ is not particularly readable.
[...]
return "(%s [] %s)" % (self.p, self.q)
which to me seems clearer, or at least easier to work out roughly what the string's going to look like.
I wish to toss out a new thought. To that end let me blow up the example to underline a scalability issue: A. q ++ " " ++ a ++ " " ++ z ++ " [" ++ m ++ " -> " ++ k ++ " |" ++ p ++ "| " ++ g ++ " -> " ++ c ++ "] " ++ h ++ " " ++ b ++ " " ++ f ++ " " ++ i B. printf "%s %s %s [%s -> %s |%s| %s -> %s] %s %s %s %s" q a z m k p g c h b f i B looks clearer because without parsing you can see that the output will contain a |blah| between two blah->blah's inside square brackets, etc. A looks clearer because without counting you can see that p is the thing that will go into |blah|, the first blah->blah will be m->k, etc. The best of both worlds may be something like the notation in the HOL theorem prover: ``^q ^a ^z [^m -> ^k |^p| ^g -> ^c] ^h ^b ^f ^i`` Do you agree that this is much better? Could someone implement something like this in GHC please? :)

I wish to toss out a new thought. To that end let me blow up the example to underline a scalability issue:
A. q ++ " " ++ a ++ " " ++ z ++ " [" ++ m ++ " -> " ++ k ++ " |" ++ p ++ "| " ++ g ++ " -> " ++ c ++ "] " ++ h ++ " " ++ b ++ " " ++ f ++ " " ++ i B. printf "%s %s %s [%s -> %s |%s| %s -> %s] %s %s %s %s" q a z m k p g c h b f i
B looks clearer because without parsing you can see that the output will contain a |blah| between two blah->blah's inside square brackets, etc.
A looks clearer because without counting you can see that p is the thing that will go into |blah|, the first blah->blah will be m->k, etc.
The best of both worlds may be something like the notation in the HOL theorem prover:
``^q ^a ^z [^m -> ^k |^p| ^g -> ^c] ^h ^b ^f ^i``
Do you agree that this is much better?
this syntax is used in Perl, and, IMHO, is very convenient. Also very convenient are HERE-docs, when user should not bother about escaping and concatenating of large strings.

Albert Lai
I wish to toss out a new thought. To that end let me blow up the example to underline a scalability issue:
A. q ++ " " ++ a ++ " " ++ z ++ " [" ++ m ++ " -> " ++ k ++ " |" ++ p ++ "| " ++ g ++ " -> " ++ c ++ "] " ++ h ++ " " ++ b ++ " " ++ f ++ " " ++ i B. printf "%s %s %s [%s -> %s |%s| %s -> %s] %s %s %s %s" q a z m k p g c h b f i
B looks clearer because without parsing you can see that the output will contain a |blah| between two blah->blah's inside square brackets, etc.
A looks clearer because without counting you can see that p is the thing that will go into |blah|, the first blah->blah will be m->k, etc.
The best of both worlds may be something like the notation in the HOL theorem prover:
``^q ^a ^z [^m -> ^k |^p| ^g -> ^c] ^h ^b ^f ^i``
Do you agree that this is much better?
Could someone implement something like this in GHC please? :)
Don't have time to work it out in detail, but something like this sounds promising:
lexToken :: String -> alpha -> (String -> String -> alpha) -> alpha lexToken (c:s) f x | isAlpha c || c == '_' = flip fix ([c], s) $ \ loop (s1, s2) -> case s2 of (c:s2') | isAlphaNum c || c == '_' || c == '\'' -> loop (c:s1, s2') _ -> f (reverse s1) s2 lexToken _ f x = x
interpolate :: String -> Q Exp interpolate [] = listE [] interpolate ('^':s) = lexToken s (fail "Expected valid Haskell identifier") $ \ s1 s2 -> infixE (Just (varE 'show `appE` varE (mkName s1))) (varE '(++)) (Just (interpolate s2)) interpolate s = let (s1, s2) = break (=='^') s in infixE (Just (litE $ StringL s1)) (varE '(++)) (Just (interpolate s2))
Call as $(interpolate "^q ^a ^z [^m -> ^k |^p| ^g -> ^c] ^h ^b ^f ^i"). Note: this is untested code! Be sure and test it before you use it (I haven't even compiled it). Confident someone can do better (e.g., formatting parameters, quoting), Jon Cast

Jonathan Cast
Albert Lai
wrote: <snip> The best of both worlds may be something like the notation in the HOL theorem prover:
``^q ^a ^z [^m -> ^k |^p| ^g -> ^c] ^h ^b ^f ^i``
Do you agree that this is much better?
Could someone implement something like this in GHC please? :)
The attached code has been tested and works; call as $(interpolate "^q ^a ^z [^m -> ^k |^p| ^g -> ^c] ^h ^b ^f ^i"). Still confident someone can do better (e.g., formatting parameters), Jon Cast
participants (8)
-
Albert Lai
-
Andy Gimblett
-
Bernard Pope
-
Bryn Keller
-
Jonathan Cast
-
Lemmih
-
Tomasz Zielonka
-
Vadim Konovalov