[Haskell-cafe] Best way to build strings?
Jonathan Cast
jcast at ou.edu
Sun Jul 24 09:59:23 EDT 2005
Albert Lai <trebla at vex.net> wrote:
<snip>
> 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
More information about the Haskell-Cafe
mailing list