initial release
[wix.git] / src / Text / PrettyPrint / Leijen.hs
1 -----------------------------------------------------------------------------
2 -- |
3 -- Module      :  Text.PrettyPrint.Leijen
4 -- Copyright   :  Daan Leijen (c) 2000, http://www.cs.uu.nl/~daan
5 -- License     :  BSD-style (see the file LICENSE)
6 --
7 -- Maintainer  :  stefanor@cox.net
8 -- Stability   :  provisional
9 -- Portability :  portable
10 --
11 -- Pretty print module based on Philip Wadler's \"prettier printer\"
12 --
13 -- @
14 --      \"A prettier printer\"
15 --      Draft paper, April 1997, revised March 1998.
16 --      <http://cm.bell-labs.com/cm/cs/who/wadler/papers/prettier/prettier.ps>
17 -- @
18 --
19 -- PPrint is an implementation of the pretty printing combinators
20 -- described by Philip Wadler (1997). In their bare essence, the
21 -- combinators of Wadler are not expressive enough to describe some
22 -- commonly occurring layouts. The PPrint library adds new primitives
23 -- to describe these layouts and works well in practice.
24 --
25 -- The library is based on a single way to concatenate documents,
26 -- which is associative and has both a left and right unit.  This
27 -- simple design leads to an efficient and short implementation. The
28 -- simplicity is reflected in the predictable behaviour of the
29 -- combinators which make them easy to use in practice.
30 --
31 -- A thorough description of the primitive combinators and their
32 -- implementation can be found in Philip Wadler's paper
33 -- (1997). Additions and the main differences with his original paper
34 -- are:
35 --
36 -- * The nil document is called empty.
37 --
38 -- * The above combinator is called '<$>'. The operator '</>' is used
39 -- for soft line breaks.
40 --
41 -- * There are three new primitives: 'align', 'fill' and
42 -- 'fillBreak'. These are very useful in practice.
43 --
44 -- * Lots of other useful combinators, like 'fillSep' and 'list'.
45 --
46 -- * There are two renderers, 'renderPretty' for pretty printing and
47 -- 'renderCompact' for compact output. The pretty printing algorithm
48 -- also uses a ribbon-width now for even prettier output.
49 --
50 -- * There are two displayers, 'displayS' for strings and 'displayIO' for
51 -- file based output.
52 --
53 -- * There is a 'Pretty' class.
54 --
55 -- * The implementation uses optimised representations and strictness
56 -- annotations.
57 --
58 -- Full documentation available at <http://www.cs.uu.nl/~daan/download/pprint/pprint.html>.
59 -----------------------------------------------------------
60 module Text.PrettyPrint.Leijen (
61    -- * Documents
62    Doc, putDoc, hPutDoc,
63
64    -- * Basic combinators
65    empty, char, text, (<>), nest, line, linebreak, group, softline,
66    softbreak,
67
68    -- * Alignment
69    --
70    -- The combinators in this section can not be described by Wadler's
71    -- original combinators. They align their output relative to the
72    -- current output position - in contrast to @nest@ which always
73    -- aligns to the current nesting level. This deprives these
74    -- combinators from being \`optimal\'. In practice however they
75    -- prove to be very useful. The combinators in this section should
76    -- be used with care, since they are more expensive than the other
77    -- combinators. For example, @align@ shouldn't be used to pretty
78    -- print all top-level declarations of a language, but using @hang@
79    -- for let expressions is fine.
80    align, hang, indent, encloseSep, list, tupled, semiBraces,
81
82    -- * Operators
83    (<+>), (<$>), (</>), (<$$>), (<//>),
84
85    -- * List combinators
86    hsep, vsep, fillSep, sep, hcat, vcat, fillCat, cat, punctuate,
87
88    -- * Fillers
89    fill, fillBreak,
90
91    -- * Bracketing combinators
92    enclose, squotes, dquotes, parens, angles, braces, brackets,
93
94    -- * Character documents
95    lparen, rparen, langle, rangle, lbrace, rbrace, lbracket, rbracket,
96    squote, dquote, semi, colon, comma, space, dot, backslash, equals,
97
98    -- * Primitive type documents
99    string, int, integer, float, double, rational,
100
101    -- * Pretty class
102    Pretty(..),
103
104    -- * Rendering
105    SimpleDoc(..), renderPretty, renderCompact, displayS, displayIO
106
107    -- * Undocumented
108         , bool
109
110         , column, nesting, width
111
112         ) where
113
114 import System.IO (Handle,hPutStr,hPutChar,stdout)
115
116 infixr 5 </>,<//>,<$>,<$$>
117 infixr 6 <>,<+>
118
119
120 -----------------------------------------------------------
121 -- list, tupled and semiBraces pretty print a list of
122 -- documents either horizontally or vertically aligned.
123 -----------------------------------------------------------
124
125
126 -- | The document @(list xs)@ comma separates the documents @xs@ and
127 -- encloses them in square brackets. The documents are rendered
128 -- horizontally if that fits the page. Otherwise they are aligned
129 -- vertically. All comma separators are put in front of the elements.
130 list :: [Doc] -> Doc
131 list            = encloseSep lbracket rbracket comma
132
133 -- | The document @(tupled xs)@ comma separates the documents @xs@ and
134 -- encloses them in parenthesis. The documents are rendered
135 -- horizontally if that fits the page. Otherwise they are aligned
136 -- vertically. All comma separators are put in front of the elements.
137 tupled :: [Doc] -> Doc
138 tupled          = encloseSep lparen   rparen  comma
139
140
141 -- | The document @(semiBraces xs)@ separates the documents @xs@ with
142 -- semi colons and encloses them in braces. The documents are rendered
143 -- horizontally if that fits the page. Otherwise they are aligned
144 -- vertically. All semi colons are put in front of the elements.
145 semiBraces :: [Doc] -> Doc
146 semiBraces      = encloseSep lbrace   rbrace  semi
147
148 -- | The document @(encloseSep l r sep xs)@ concatenates the documents
149 -- @xs@ separated by @sep@ and encloses the resulting document by @l@
150 -- and @r@. The documents are rendered horizontally if that fits the
151 -- page. Otherwise they are aligned vertically. All separators are put
152 -- in front of the elements. For example, the combinator 'list' can be
153 -- defined with @encloseSep@:
154 --
155 -- > list xs = encloseSep lbracket rbracket comma xs
156 -- > test    = text "list" <+> (list (map int [10,200,3000]))
157 --
158 -- Which is layed out with a page width of 20 as:
159 --
160 -- @
161 -- list [10,200,3000]
162 -- @
163 --
164 -- But when the page width is 15, it is layed out as:
165 --
166 -- @
167 -- list [10
168 --      ,200
169 --      ,3000]
170 -- @
171 encloseSep :: Doc -> Doc -> Doc -> [Doc] -> Doc
172 encloseSep left right sep ds
173     = case ds of
174         []  -> left <> right
175         [d] -> left <> d <> right
176         _   -> align (cat (zipWith (<>) (left : repeat sep) ds) <> right) 
177
178
179 -----------------------------------------------------------
180 -- punctuate p [d1,d2,...,dn] => [d1 <> p,d2 <> p, ... ,dn]
181 -----------------------------------------------------------
182
183
184 -- | @(punctuate p xs)@ concatenates all documents in @xs@ with
185 -- document @p@ except for the last document.
186 --
187 -- > someText = map text ["words","in","a","tuple"]
188 -- > test     = parens (align (cat (punctuate comma someText)))
189 --
190 -- This is layed out on a page width of 20 as:
191 --
192 -- @
193 -- (words,in,a,tuple)
194 -- @
195 --
196 -- But when the page width is 15, it is layed out as:
197 --
198 -- @
199 -- (words,
200 --  in,
201 --  a,
202 --  tuple)
203 -- @
204 --
205 -- (If you want put the commas in front of their elements instead of
206 -- at the end, you should use 'tupled' or, in general, 'encloseSep'.)
207 punctuate :: Doc -> [Doc] -> [Doc]
208 punctuate p []      = []
209 punctuate p [d]     = [d]
210 punctuate p (d:ds)  = (d <> p) : punctuate p ds
211
212
213 -----------------------------------------------------------
214 -- high-level combinators
215 -----------------------------------------------------------
216
217
218 -- | The document @(sep xs)@ concatenates all documents @xs@ either
219 -- horizontally with @(\<+\>)@, if it fits the page, or vertically with
220 -- @(\<$\>)@.
221 --
222 -- > sep xs  = group (vsep xs)
223 sep :: [Doc] -> Doc
224 sep             = group . vsep
225
226 -- | The document @(fillSep xs)@ concatenates documents @xs@
227 -- horizontally with @(\<+\>)@ as long as its fits the page, than
228 -- inserts a @line@ and continues doing that for all documents in
229 -- @xs@.
230 --
231 -- > fillSep xs  = foldr (\<\/\>) empty xs
232 fillSep :: [Doc] -> Doc
233 fillSep         = fold (</>)
234
235 -- | The document @(hsep xs)@ concatenates all documents @xs@
236 -- horizontally with @(\<+\>)@.
237 hsep :: [Doc] -> Doc
238 hsep            = fold (<+>)
239
240
241 -- | The document @(vsep xs)@ concatenates all documents @xs@
242 -- vertically with @(\<$\>)@. If a 'group' undoes the line breaks
243 -- inserted by @vsep@, all documents are separated with a space.
244 --
245 -- > someText = map text (words ("text to lay out"))
246 -- >
247 -- > test     = text "some" <+> vsep someText
248 --
249 -- This is layed out as:
250 --
251 -- @
252 -- some text
253 -- to
254 -- lay
255 -- out
256 -- @
257 --
258 -- The 'align' combinator can be used to align the documents under
259 -- their first element
260 --
261 -- > test     = text "some" <+> align (vsep someText)
262 --
263 -- Which is printed as:
264 --
265 -- @
266 -- some text
267 --      to
268 --      lay
269 --      out
270 -- @
271 vsep :: [Doc] -> Doc
272 vsep            = fold (<$>)
273
274 -- | The document @(cat xs)@ concatenates all documents @xs@ either
275 -- horizontally with @(\<\>)@, if it fits the page, or vertically with
276 -- @(\<$$\>)@.
277 --
278 -- > cat xs  = group (vcat xs)
279 cat :: [Doc] -> Doc
280 cat             = group . vcat
281
282 -- | The document @(fillCat xs)@ concatenates documents @xs@
283 -- horizontally with @(\<\>)@ as long as its fits the page, than inserts
284 -- a @linebreak@ and continues doing that for all documents in @xs@.
285 --
286 -- > fillCat xs  = foldr (\<\/\/\>) empty xs
287 fillCat :: [Doc] -> Doc
288 fillCat         = fold (<//>)
289
290 -- | The document @(hcat xs)@ concatenates all documents @xs@
291 -- horizontally with @(\<\>)@.
292 hcat :: [Doc] -> Doc
293 hcat            = fold (<>)
294
295 -- | The document @(vcat xs)@ concatenates all documents @xs@
296 -- vertically with @(\<$$\>)@. If a 'group' undoes the line breaks
297 -- inserted by @vcat@, all documents are directly concatenated.
298 vcat :: [Doc] -> Doc
299 vcat            = fold (<$$>)
300
301 fold f []       = empty
302 fold f ds       = foldr1 f ds
303
304 -- | The document @(x \<\> y)@ concatenates document @x@ and document
305 -- @y@. It is an associative operation having 'empty' as a left and
306 -- right unit.  (infixr 6)
307 (<>) :: Doc -> Doc -> Doc
308 x <> y          = x `beside` y
309
310 -- | The document @(x \<+\> y)@ concatenates document @x@ and @y@ with a
311 -- @space@ in between.  (infixr 6)
312 (<+>) :: Doc -> Doc -> Doc
313 x <+> y         = x <> space <> y
314
315 -- | The document @(x \<\/\> y)@ concatenates document @x@ and @y@ with a
316 -- 'softline' in between. This effectively puts @x@ and @y@ either
317 -- next to each other (with a @space@ in between) or underneath each
318 -- other. (infixr 5)
319 (</>) :: Doc -> Doc -> Doc
320 x </> y         = x <> softline <> y
321
322 -- | The document @(x \<\/\/\> y)@ concatenates document @x@ and @y@ with
323 -- a 'softbreak' in between. This effectively puts @x@ and @y@ either
324 -- right next to each other or underneath each other. (infixr 5)
325 (<//>) :: Doc -> Doc -> Doc
326 x <//> y        = x <> softbreak <> y
327
328 -- | The document @(x \<$\> y)@ concatenates document @x@ and @y@ with a
329 -- 'line' in between. (infixr 5)
330 (<$>) :: Doc -> Doc -> Doc
331 x <$> y         = x <> line <> y
332
333 -- | The document @(x \<$$\> y)@ concatenates document @x@ and @y@ with
334 -- a @linebreak@ in between. (infixr 5)
335 (<$$>) :: Doc -> Doc -> Doc
336 x <$$> y        = x <> linebreak <> y
337
338 -- | The document @softline@ behaves like 'space' if the resulting
339 -- output fits the page, otherwise it behaves like 'line'.
340 --
341 -- > softline = group line
342 softline :: Doc
343 softline        = group line
344
345 -- | The document @softbreak@ behaves like 'empty' if the resulting
346 -- output fits the page, otherwise it behaves like 'line'.
347 --
348 -- > softbreak  = group linebreak
349 softbreak :: Doc
350 softbreak       = group linebreak
351
352 -- | Document @(squotes x)@ encloses document @x@ with single quotes
353 -- \"'\".
354 squotes :: Doc -> Doc
355 squotes         = enclose squote squote
356
357 -- | Document @(dquotes x)@ encloses document @x@ with double quotes
358 -- '\"'.
359 dquotes :: Doc -> Doc
360 dquotes         = enclose dquote dquote
361
362 -- | Document @(braces x)@ encloses document @x@ in braces, \"{\" and
363 -- \"}\".
364 braces :: Doc -> Doc
365 braces          = enclose lbrace rbrace
366
367 -- | Document @(parens x)@ encloses document @x@ in parenthesis, \"(\"
368 -- and \")\".
369 parens :: Doc -> Doc
370 parens          = enclose lparen rparen
371
372 -- | Document @(angles x)@ encloses document @x@ in angles, \"\<\" and
373 -- \"\>\".
374 angles :: Doc -> Doc
375 angles          = enclose langle rangle
376
377 -- | Document @(brackets x)@ encloses document @x@ in square brackets,
378 -- \"[\" and \"]\".
379 brackets :: Doc -> Doc
380 brackets        = enclose lbracket rbracket
381
382 -- | The document @(enclose l r x)@ encloses document @x@ between
383 -- documents @l@ and @r@ using @(\<\>)@.
384 --
385 -- > enclose l r x   = l <> x <> r
386 enclose :: Doc -> Doc -> Doc -> Doc
387 enclose l r x   = l <> x <> r
388
389 -- | The document @lparen@ contains a left parenthesis, \"(\".
390 lparen :: Doc
391 lparen          = char '('
392 -- | The document @rparen@ contains a right parenthesis, \")\".
393 rparen :: Doc
394 rparen          = char ')'
395 -- | The document @langle@ contains a left angle, \"\<\".
396 langle :: Doc
397 langle          = char '<'
398 -- | The document @rangle@ contains a right angle, \">\".
399 rangle :: Doc
400 rangle          = char '>'
401 -- | The document @lbrace@ contains a left brace, \"{\".
402 lbrace :: Doc
403 lbrace          = char '{'
404 -- | The document @rbrace@ contains a right brace, \"}\".
405 rbrace :: Doc
406 rbrace          = char '}'
407 -- | The document @lbracket@ contains a left square bracket, \"[\".
408 lbracket :: Doc
409 lbracket        = char '['
410 -- | The document @rbracket@ contains a right square bracket, \"]\".
411 rbracket :: Doc
412 rbracket        = char ']'
413
414
415 -- | The document @squote@ contains a single quote, \"'\".
416 squote :: Doc
417 squote          = char '\''
418 -- | The document @dquote@ contains a double quote, '\"'.
419 dquote :: Doc
420 dquote          = char '"'
421 -- | The document @semi@ contains a semi colon, \";\".
422 semi :: Doc
423 semi            = char ';'
424 -- | The document @colon@ contains a colon, \":\".
425 colon :: Doc
426 colon           = char ':'
427 -- | The document @comma@ contains a comma, \",\".
428 comma :: Doc
429 comma           = char ','
430 -- | The document @space@ contains a single space, \" \".
431 --
432 -- > x <+> y   = x <> space <> y
433 space :: Doc
434 space           = char ' '
435 -- | The document @dot@ contains a single dot, \".\".
436 dot :: Doc
437 dot             = char '.'
438 -- | The document @backslash@ contains a back slash, \"\\\".
439 backslash :: Doc
440 backslash       = char '\\'
441 -- | The document @equals@ contains an equal sign, \"=\".
442 equals :: Doc
443 equals          = char '='
444
445
446 -----------------------------------------------------------
447 -- Combinators for prelude types
448 -----------------------------------------------------------
449
450 -- string is like "text" but replaces '\n' by "line"
451
452 -- | The document @(string s)@ concatenates all characters in @s@
453 -- using @line@ for newline characters and @char@ for all other
454 -- characters. It is used instead of 'text' whenever the text contains
455 -- newline characters.
456 string :: String -> Doc
457 string ""       = empty
458 string ('\n':s) = line <> string s
459 string s        = case (span (/='\n') s) of
460                     (xs,ys) -> text xs <> string ys
461
462 bool :: Bool -> Doc
463 bool b          = text (show b)
464
465 -- | The document @(int i)@ shows the literal integer @i@ using
466 -- 'text'.
467 int :: Int -> Doc
468 int i           = text (show i)
469
470 -- | The document @(integer i)@ shows the literal integer @i@ using
471 -- 'text'.
472 integer :: Integer -> Doc
473 integer i       = text (show i)
474
475 -- | The document @(float f)@ shows the literal float @f@ using
476 -- 'text'.
477 float :: Float -> Doc
478 float f         = text (show f)
479
480 -- | The document @(double d)@ shows the literal double @d@ using
481 -- 'text'.
482 double :: Double -> Doc
483 double d        = text (show d)
484
485 -- | The document @(rational r)@ shows the literal rational @r@ using
486 -- 'text'.
487 rational :: Rational -> Doc
488 rational r      = text (show r)
489
490
491 -----------------------------------------------------------
492 -- overloading "pretty"
493 -----------------------------------------------------------
494
495 -- | The member @prettyList@ is only used to define the @instance Pretty
496 -- a => Pretty [a]@. In normal circumstances only the @pretty@ function
497 -- is used.
498 class Pretty a where
499   pretty        :: a -> Doc
500   prettyList    :: [a] -> Doc
501   prettyList    = list . map pretty
502
503 instance Pretty a => Pretty [a] where
504   pretty        = prettyList
505
506 instance Pretty Doc where
507   pretty        = id
508
509 instance Pretty () where
510   pretty ()     = text "()"
511
512 instance Pretty Bool where
513   pretty b      = bool b
514
515 instance Pretty Char where
516   pretty c      = char c
517   prettyList s  = string s
518
519 instance Pretty Int where
520   pretty i      = int i
521
522 instance Pretty Integer where
523   pretty i      = integer i
524
525 instance Pretty Float where
526   pretty f      = float f
527
528 instance Pretty Double where
529   pretty d      = double d
530
531
532 --instance Pretty Rational where
533 --  pretty r      = rational r
534
535 instance (Pretty a,Pretty b) => Pretty (a,b) where
536   pretty (x,y)  = tupled [pretty x, pretty y]
537
538 instance (Pretty a,Pretty b,Pretty c) => Pretty (a,b,c) where
539   pretty (x,y,z)= tupled [pretty x, pretty y, pretty z]
540
541 instance Pretty a => Pretty (Maybe a) where
542   pretty Nothing        = empty
543   pretty (Just x)       = pretty x
544
545
546
547 -----------------------------------------------------------
548 -- semi primitive: fill and fillBreak
549 -----------------------------------------------------------
550
551 -- | The document @(fillBreak i x)@ first renders document @x@. It
552 -- than appends @space@s until the width is equal to @i@. If the
553 -- width of @x@ is already larger than @i@, the nesting level is
554 -- increased by @i@ and a @line@ is appended. When we redefine @ptype@
555 -- in the previous example to use @fillBreak@, we get a useful
556 -- variation of the previous output:
557 --
558 -- > ptype (name,tp)
559 -- >        = fillBreak 6 (text name) <+> text "::" <+> text tp
560 --
561 -- The output will now be:
562 --
563 -- @
564 -- let empty  :: Doc
565 --     nest   :: Int -> Doc -> Doc
566 --     linebreak
567 --            :: Doc
568 -- @
569 fillBreak :: Int -> Doc -> Doc
570 fillBreak f x   = width x (\w ->
571                   if (w > f) then nest f linebreak
572                              else text (spaces (f - w)))
573
574
575 -- | The document @(fill i x)@ renders document @x@. It than appends
576 -- @space@s until the width is equal to @i@. If the width of @x@ is
577 -- already larger, nothing is appended. This combinator is quite
578 -- useful in practice to output a list of bindings. The following
579 -- example demonstrates this.
580 --
581 -- > types  = [("empty","Doc")
582 -- >          ,("nest","Int -> Doc -> Doc")
583 -- >          ,("linebreak","Doc")]
584 -- >
585 -- > ptype (name,tp)
586 -- >        = fill 6 (text name) <+> text "::" <+> text tp
587 -- >
588 -- > test   = text "let" <+> align (vcat (map ptype types))
589 --
590 -- Which is layed out as:
591 --
592 -- @
593 -- let empty  :: Doc
594 --     nest   :: Int -> Doc -> Doc
595 --     linebreak :: Doc
596 -- @
597 fill :: Int -> Doc -> Doc
598 fill f d        = width d (\w ->
599                   if (w >= f) then empty
600                               else text (spaces (f - w)))
601
602 width :: Doc -> (Int -> Doc) -> Doc
603 width d f       = column (\k1 -> d <> column (\k2 -> f (k2 - k1)))
604
605
606 -----------------------------------------------------------
607 -- semi primitive: Alignment and indentation
608 -----------------------------------------------------------
609
610 -- | The document @(indent i x)@ indents document @x@ with @i@ spaces.
611 --
612 -- > test  = indent 4 (fillSep (map text
613 -- >         (words "the indent combinator indents these words !")))
614 --
615 -- Which lays out with a page width of 20 as:
616 --
617 -- @
618 --     the indent
619 --     combinator
620 --     indents these
621 --     words !
622 -- @
623 indent :: Int -> Doc -> Doc
624 indent i d      = hang i (text (spaces i) <> d)
625
626 -- | The hang combinator implements hanging indentation. The document
627 -- @(hang i x)@ renders document @x@ with a nesting level set to the
628 -- current column plus @i@. The following example uses hanging
629 -- indentation for some text:
630 --
631 -- > test  = hang 4 (fillSep (map text
632 -- >         (words "the hang combinator indents these words !")))
633 --
634 -- Which lays out on a page with a width of 20 characters as:
635 --
636 -- @
637 -- the hang combinator
638 --     indents these
639 --     words !
640 -- @
641 --
642 -- The @hang@ combinator is implemented as:
643 --
644 -- > hang i x  = align (nest i x)
645 hang :: Int -> Doc -> Doc
646 hang i d        = align (nest i d)
647
648 -- | The document @(align x)@ renders document @x@ with the nesting
649 -- level set to the current column. It is used for example to
650 -- implement 'hang'.
651 --
652 -- As an example, we will put a document right above another one,
653 -- regardless of the current nesting level:
654 --
655 -- > x $$ y  = align (x <$> y)
656 --
657 -- > test    = text "hi" <+> (text "nice" $$ text "world")
658 --
659 -- which will be layed out as:
660 --
661 -- @
662 -- hi nice
663 --    world
664 -- @
665 align :: Doc -> Doc
666 align d         = column (\k ->
667                   nesting (\i -> nest (k - i) d))   --nesting might be negative :-)
668
669
670
671 -----------------------------------------------------------
672 -- Primitives
673 -----------------------------------------------------------
674
675 -- | The abstract data type @Doc@ represents pretty documents.
676 --
677 -- @Doc@ is an instance of the 'Show' class. @(show doc)@ pretty
678 -- prints document @doc@ with a page width of 100 characters and a
679 -- ribbon width of 40 characters.
680 --
681 -- > show (text "hello" <$> text "world")
682 --
683 -- Which would return the string \"hello\\nworld\", i.e.
684 --
685 -- @
686 -- hello
687 -- world
688 -- @
689 data Doc        = Empty
690                 | Char Char             -- invariant: char is not '\n'
691                 | Text !Int String      -- invariant: text doesn't contain '\n'
692                 | Line !Bool            -- True <=> when undone by group, do not insert a space
693                 | Cat Doc Doc
694                 | Nest !Int Doc
695                 | Union Doc Doc         -- invariant: first lines of first doc longer than the first lines of the second doc
696                 | Column  (Int -> Doc)
697                 | Nesting (Int -> Doc)
698
699
700 -- | The data type @SimpleDoc@ represents rendered documents and is
701 -- used by the display functions.
702 --
703 -- The @Int@ in @SText@ contains the length of the string. The @Int@
704 -- in @SLine@ contains the indentation for that line. The library
705 -- provides two default display functions 'displayS' and
706 -- 'displayIO'. You can provide your own display function by writing a
707 -- function from a @SimpleDoc@ to your own output format.
708 data SimpleDoc  = SEmpty
709                 | SChar Char SimpleDoc
710                 | SText !Int String SimpleDoc
711                 | SLine !Int SimpleDoc
712
713
714 -- | The empty document is, indeed, empty. Although @empty@ has no
715 -- content, it does have a \'height\' of 1 and behaves exactly like
716 -- @(text \"\")@ (and is therefore not a unit of @\<$\>@).
717 empty :: Doc
718 empty           = Empty
719
720 -- | The document @(char c)@ contains the literal character @c@. The
721 -- character shouldn't be a newline (@'\n'@), the function 'line'
722 -- should be used for line breaks.
723 char :: Char -> Doc
724 char '\n'       = line
725 char c          = Char c
726
727 -- | The document @(text s)@ contains the literal string @s@. The
728 -- string shouldn't contain any newline (@'\n'@) characters. If the
729 -- string contains newline characters, the function 'string' should be
730 -- used.
731 text :: String -> Doc
732 text ""         = Empty
733 text s          = Text (length s) s
734
735 -- | The @line@ document advances to the next line and indents to the
736 -- current nesting level. Document @line@ behaves like @(text \" \")@
737 -- if the line break is undone by 'group'.
738 line :: Doc
739 line            = Line False
740
741 -- | The @linebreak@ document advances to the next line and indents to
742 -- the current nesting level. Document @linebreak@ behaves like
743 -- 'empty' if the line break is undone by 'group'.
744 linebreak :: Doc
745 linebreak       = Line True
746
747 beside x y      = Cat x y
748
749 -- | The document @(nest i x)@ renders document @x@ with the current
750 -- indentation level increased by i (See also 'hang', 'align' and
751 -- 'indent').
752 --
753 -- > nest 2 (text "hello" <$> text "world") <$> text "!"
754 --
755 -- outputs as:
756 --
757 -- @
758 -- hello
759 --   world
760 -- !
761 -- @
762 nest :: Int -> Doc -> Doc
763 nest i x        = Nest i x
764
765 column, nesting :: (Int -> Doc) -> Doc
766 column f        = Column f
767 nesting f       = Nesting f
768
769 -- | The @group@ combinator is used to specify alternative
770 -- layouts. The document @(group x)@ undoes all line breaks in
771 -- document @x@. The resulting line is added to the current line if
772 -- that fits the page. Otherwise, the document @x@ is rendered without
773 -- any changes.
774 group :: Doc -> Doc
775 group x         = Union (flatten x) x
776
777 flatten :: Doc -> Doc
778 flatten (Cat x y)       = Cat (flatten x) (flatten y)
779 flatten (Nest i x)      = Nest i (flatten x)
780 flatten (Line break)    = if break then Empty else Text 1 " "
781 flatten (Union x y)     = flatten x
782 flatten (Column f)      = Column (flatten . f)
783 flatten (Nesting f)     = Nesting (flatten . f)
784 flatten other           = other                     --Empty,Char,Text
785
786
787
788 -----------------------------------------------------------
789 -- Renderers
790 -----------------------------------------------------------
791
792 -----------------------------------------------------------
793 -- renderPretty: the default pretty printing algorithm
794 -----------------------------------------------------------
795
796 -- list of indentation/document pairs; saves an indirection over [(Int,Doc)]
797 data Docs   = Nil
798             | Cons !Int Doc Docs
799
800
801 -- | This is the default pretty printer which is used by 'show',
802 -- 'putDoc' and 'hPutDoc'. @(renderPretty ribbonfrac width x)@ renders
803 -- document @x@ with a page width of @width@ and a ribbon width of
804 -- @(ribbonfrac * width)@ characters. The ribbon width is the maximal
805 -- amount of non-indentation characters on a line. The parameter
806 -- @ribbonfrac@ should be between @0.0@ and @1.0@. If it is lower or
807 -- higher, the ribbon width will be 0 or @width@ respectively.
808 renderPretty :: Float -> Int -> Doc -> SimpleDoc
809 renderPretty rfrac w x
810     = best 0 0 (Cons 0 x Nil)
811     where
812       -- r :: the ribbon width in characters
813       r  = max 0 (min w (round (fromIntegral w * rfrac)))
814
815       -- best :: n = indentation of current line
816       --         k = current column
817       --        (ie. (k >= n) && (k - n == count of inserted characters)
818       best n k Nil      = SEmpty
819       best n k (Cons i d ds)
820         = case d of
821             Empty       -> best n k ds
822             Char c      -> let k' = k+1 in seq k' (SChar c (best n k' ds))
823             Text l s    -> let k' = k+l in seq k' (SText l s (best n k' ds))
824             Line _      -> SLine i (best i i ds)
825             Cat x y     -> best n k (Cons i x (Cons i y ds))
826             Nest j x    -> let i' = i+j in seq i' (best n k (Cons i' x ds))
827             Union x y   -> nicest n k (best n k (Cons i x ds))
828                                       (best n k (Cons i y ds))
829
830             Column f    -> best n k (Cons i (f k) ds)
831             Nesting f   -> best n k (Cons i (f i) ds)
832
833       --nicest :: r = ribbon width, w = page width,
834       --          n = indentation of current line, k = current column
835       --          x and y, the (simple) documents to chose from.
836       --          precondition: first lines of x are longer than the first lines of y.
837       nicest n k x y    | fits width x  = x
838                         | otherwise     = y
839                         where
840                           width = min (w - k) (r - k + n)
841
842
843 fits w x        | w < 0         = False
844 fits w SEmpty                   = True
845 fits w (SChar c x)              = fits (w - 1) x
846 fits w (SText l s x)            = fits (w - l) x
847 fits w (SLine i x)              = True
848
849
850 -----------------------------------------------------------
851 -- renderCompact: renders documents without indentation
852 --  fast and fewer characters output, good for machines
853 -----------------------------------------------------------
854
855
856 -- | @(renderCompact x)@ renders document @x@ without adding any
857 -- indentation. Since no \'pretty\' printing is involved, this
858 -- renderer is very fast. The resulting output contains fewer
859 -- characters than a pretty printed version and can be used for output
860 -- that is read by other programs.
861 renderCompact :: Doc -> SimpleDoc
862 renderCompact x
863     = scan 0 [x]
864     where
865       scan k []     = SEmpty
866       scan k (d:ds) = case d of
867                         Empty       -> scan k ds
868                         Char c      -> let k' = k+1 in seq k' (SChar c (scan k' ds))
869                         Text l s    -> let k' = k+l in seq k' (SText l s (scan k' ds))
870                         Line _      -> SLine 0 (scan 0 ds)
871                         Cat x y     -> scan k (x:y:ds)
872                         Nest j x    -> scan k (x:ds)
873                         Union x y   -> scan k (y:ds)
874                         Column f    -> scan k (f k:ds)
875                         Nesting f   -> scan k (f 0:ds)
876
877
878
879 -----------------------------------------------------------
880 -- Displayers:  displayS and displayIO
881 -----------------------------------------------------------
882
883
884 -- | @(displayS simpleDoc)@ takes the output @simpleDoc@ from a
885 -- rendering function and transforms it to a 'ShowS' type (for use in
886 -- the 'Show' class).
887 --
888 -- > showWidth :: Int -> Doc -> String
889 -- > showWidth w x   = displayS (renderPretty 0.4 w x) ""
890 displayS :: SimpleDoc -> ShowS
891 displayS SEmpty             = id
892 displayS (SChar c x)        = showChar c . displayS x
893 displayS (SText l s x)      = showString s . displayS x
894 displayS (SLine i x)        = showString ('\n':indentation i) . displayS x
895
896
897 -- | @(displayIO handle simpleDoc)@ writes @simpleDoc@ to the file
898 -- handle @handle@. This function is used for example by 'hPutDoc':
899 --
900 -- > hPutDoc handle doc  = displayIO handle (renderPretty 0.4 100 doc)
901 displayIO :: Handle -> SimpleDoc -> IO ()
902 displayIO handle simpleDoc
903     = display simpleDoc
904     where
905       display SEmpty        = return ()
906       display (SChar c x)   = do{ hPutChar handle c; display x}
907       display (SText l s x) = do{ hPutStr handle s; display x}
908       display (SLine i x)   = do{ hPutStr handle ('\n':indentation i); display x}
909
910
911 -----------------------------------------------------------
912 -- default pretty printers: show, putDoc and hPutDoc
913 -----------------------------------------------------------
914 instance Show Doc where
915   showsPrec d doc       = displayS (renderPretty 0.4 80 doc)
916
917 -- | The action @(putDoc doc)@ pretty prints document @doc@ to the
918 -- standard output, with a page width of 100 characters and a ribbon
919 -- width of 40 characters.
920 --
921 -- > main :: IO ()
922 -- > main = do{ putDoc (text "hello" <+> text "world") }
923 --
924 -- Which would output
925 --
926 -- @
927 -- hello world
928 -- @
929 putDoc :: Doc -> IO ()
930 putDoc doc              = hPutDoc stdout doc
931
932 -- | @(hPutDoc handle doc)@ pretty prints document @doc@ to the file
933 -- handle @handle@ with a page width of 100 characters and a ribbon
934 -- width of 40 characters.
935 --
936 -- > main = do{ handle <- openFile "MyFile" WriteMode
937 -- >          ; hPutDoc handle (vcat (map text
938 -- >                            ["vertical","text"]))
939 -- >          ; hClose handle
940 -- >          }
941 hPutDoc :: Handle -> Doc -> IO ()
942 hPutDoc handle doc      = displayIO handle (renderPretty 0.4 80 doc)
943
944
945
946 -----------------------------------------------------------
947 -- insert spaces
948 -- "indentation" used to insert tabs but tabs seem to cause
949 -- more trouble than they solve :-)
950 -----------------------------------------------------------
951 spaces n        | n <= 0    = ""
952                 | otherwise = replicate n ' '
953
954 indentation n   = spaces n
955
956 --indentation n   | n >= 8    = '\t' : indentation (n-8)
957 --                | otherwise = spaces n
958
959 --  LocalWords:  PPrint combinators Wadler Wadler's encloseSep