[Haskell-cafe] Request for a Simple Pretty Printing library

Doaitse Swierstra doaitse at cs.uu.nl
Wed Dec 13 16:49:09 EST 2006


The Prettyprint library you can download from:

http://www.cs.uu.nl/wiki/HUT/Download

and is described on:

http://www.cs.uu.nl/wiki/HUT/PrettyPrintingCombinators

contains amongst others the following code:

data Doc        = Empty
                 | Char Char             -- invariant: char is not '\n'
                 | Text !Int String      -- invariant: text doesn't  
contain '\n'
                 | Line !Bool            -- True <=> when undone by  
group, do not insert a space
                 | Cat Doc Doc
                 | Nest !Int Doc
                 | Union Doc Doc         -- invariant: first lines of  
first doc longer than the first lines of the second doc
                 | Column  (Int -> Doc)
                 | Nesting (Int -> Doc)

text ""         = Empty
text s          = Text (length s) s

so if you define now:

wrap l t r = Text 0 l <|> text t <|> Text 0 r

you should be set and done,

  Doaitse Swierstra


On Dec 13, 2006, at 10:31 PM, Tomasz Zielonka wrote:
> On Wed, Dec 13, 2006 at 08:58:25PM +0000, Neil Mitchell wrote:
>> I've been using the HughesPJ pretty printing library, but I need a  
>> new
>> combinator:
>>
>> wrap :: String -> Doc -> String -> Doc
>> wrap prepend doc append = ...
>>
>> The semantics of this would be that the text is prepended and  
>> appended
>> to the doc when rendered, but does not alter the pretty printing at
>> all. The idea of this is to support printing with HTML rendering:
>>
>> wrap "<span class='keyword'>" (text "case") "</span>"
>>
>> The HughesPJ library is 1000 lines long, so will be quite a lot of
>> work to change this to get it working properly.
>
> I am not sure it will work, but it's sufficiently easy to try.
> Look at the innards of HughesPJ, especially the TextBeside data
> constructor. Its second parameter is an Int holding the length
> of the text. Perhaps if you created TextBeside with your HTML
> markup, but with 0 length field, things would be laid out properly.
>
> Something like:
>
> wrap prepend doc append =
>     zeroText prepend <> doc <> zeroText append
> zeroText s = textBeside_ (Str s) 0 Empty
>
> Best regards
> Tomasz
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe






More information about the Haskell-Cafe mailing list