[Haskell-cafe] Language.Haskell and strings

Sterling Clover s.clover at gmail.com
Sun Sep 21 21:46:04 EDT 2008


A quick glance at the code reveals that there's an instance of Pretty  
like such:

instance Pretty HsLiteral where
	pretty (HsInt i)        = integer i
	pretty (HsChar c)       = text (show c)
	pretty (HsString s)     = text (show s)
	pretty (HsFrac r)       = double (fromRational r)

That HsString instance is wrong for what you want, but there doesn't  
seem any way to simply override it. It should, however, be easy  
enough to add a further postprocessing layer to your already pretty- 
printed text, looking line by line for those lines that are a) too  
long and b) contain a very large quoted string. This layer could  
fairly easily do something reasonable to break the string up.  
Alternately, you could write a preprocessing layer that walked the  
source tree directly and chunked all HsStrings over a certain length  
into "aaaa" ++ "aaaa" ++ "aaaa", etc. At which point, the pretty  
printer could then decide how to distribute them properly across  
lines. Neither would be as perfect a solution as integrating with the  
pretty printer directly, but both would be helpful, and the latter  
could probably even be a one or two liner with an appropriate use of  
SYB.

--Sterl


On Sep 21, 2008, at 5:37 PM, Sukit Tretriluxana wrote:

> Data.List
>
> prettyStr :: Int -> String -> IO ()
> prettyStr maxlen str = do
>    putStr ("\"" ++ head brokenStr)
>    mapM_ (\str -> putStr ("\\\n\\" ++ str)) (tail brokenStr)
>    putStr "\"\n"
>    where brokenStr = map (snd.unzip) $ groupBy (\_ (i,_) -> i `mod`  
> maxlen /= 0) $ zip [0..] str
>
> Ed
>
> On Sat, Sep 20, 2008 at 4:14 PM, Maurí cio  
> <briqueabraque at yahoo.com> wrote:
> Hi,
>
> I'm using Language.Haskell.* and would
> like to know if it's possible to
> pretty-print big strings like this:
>
> "aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa"
>
> into something like this:
>
> "aaaaaaaa\
> \aaaaaaaa\
> \aaaaaaaa\
> \aaaaaaaa\
> \aaaaaaaa\
> \aaaaaaaa\



More information about the Haskell-Cafe mailing list