In an attempt to gather experience with Philip Wadlers pretty printing
combinators, I converted a semi big pretty printer to his pretty
printing. My initial experiences are positive: while Phil's
combinators are clearly less expressive, they were expressive enough
(at least with the improvements below) and the results was subjectly
clearer.
For the utility of others which might wish to experiment I include my
library, apologizing up front from the lack of clean-up,
documentation, and optimization.
On an unrelated note, I like to add that I consider it a feature, not
a bug, that combinators build a Doc structure, as this enables a later
unforseen interpretation of the document. Such an interpretation
could be for proportional fonts, colors, etc.
/Tommy
-----------------------------------------------------------------------
Philip Wadlers Simplified Pretty Printing Library
Hacked somewhat to pieces by Tommy Thorn, 26/3-1998
Major changes:
- <+> and $$ has nil (empty) as unit.
- bline is a blind line that disappears when flattened
> module WadlersPretty where
> infixr 5 :<|>
> infixr 6 :<>
> infixr 6 <>, <+>
> infixr 5 </>, $$
> data Doc = Nil
> | Doc :<> Doc
> | Nest Int Doc
> | Text String
> | Line
> | BLine -- blind line
> | Doc :<|> Doc
>
> data DOC = NIL
> | String `TEXT` DOC
> | Int `LINE` DOC
>
>
> nil = Nil
Maintain canonical form
> Nil <> y = y
> x <> Nil = x
> x <> y = x :<> y
> nest k Nil = Nil
> nest k x = Nest k x
`text ""' is not the same as nil
> text = Text
> line = Line
> bline = BLine
> group x = flatten x :<|> x
>
> flatten Nil = Nil
> flatten (x :<> y) = flatten x :<> flatten y
> flatten (Nest i x) = Nest i (flatten x)
> flatten (Text s) = Text s
> flatten Line = Text " "
> flatten BLine = Nil
> flatten (x :<|> y) = flatten x
>
> layout NIL = ""
> layout (s `TEXT` x) = s ++ layout x
> layout (i `LINE` x) = '\n' : copy i ' ' ++ layout x
>
> copy i x = [ x | _ <- [1..i] ]
>
> best w k x = be w k [(0,x)]
>
> be w k [] = NIL
> be w k ((i,Nil):z) = be w k z
> be w k ((i,x :<> y):z) = be w k ((i,x):(i,y):z)
> be w k ((i,Nest j x):z) = be w k ((i+j,x):z)
> be w k ((i,Text s):z) = s `TEXT` be w (k+length s) z
> be w k ((i,Line):z) = i `LINE` be w i z
> be w k ((i,BLine):z) = i `LINE` be w i z
> be w k ((i,x :<|> y):z) = better w k (be w k ((i,x):z)) (be w k ((i,y):z))
>
> better w k x y = if fits (w-k) x then x else y
>
> fits w x | w < 0 = False
> fits w NIL = True
> fits w (s `TEXT` x) = fits (w - length s) x
> fits w (i `LINE` x) = True
A Pretty Class
> class Pretty a where pretty :: a -> Doc
> instance Pretty Char where pretty c = text [c]
> instance Pretty Int where pretty n = text (show n)
Utilities
> Nil <+> y = y
> x <+> Nil = x
> x <+> y = x <> space <> y
> Nil $$ x = x
> x $$ Nil = x
> x $$ y = x <> line <> y
> x </> y = x <> line <> y -- force a newline
> punctuate sep [] = nil
> punctuate sep [x] = x
> punctuate sep (x:xs) = x <> sep <> punctuate sep xs
> vcat = punctuate line
> sep x = group (vcat x)
> parens x = text "(" <> x <> text ")"
> brackets x = text "[" <> x <> text "]"
> braces x = text "{" <> x <> text "}"
> empty = nil
> space = text " "
> period = text "."
> comma = text ","
> semi = text ";"
> colon = text ":"
> int :: Int -> Doc
> int n = text (show n)
> char :: Char -> Doc
> char n = text [n]
> instance Show Doc where
> showsPrec _ x = showString (layout (best 79 0 x))
> putDoc :: Doc -> IO ()
> putDoc x = putStr (layout (best 79 0 x))