[project @ 2002-05-15 12:17:18 by simonmar]
[haskell-directory.git] / Text / PrettyPrint / HughesPJ.hs
1 -----------------------------------------------------------------------------
2 -- |
3 -- Module      :  Text.PrettyPrint.HughesPJ
4 -- Copyright   :  (c) The University of Glasgow 2001
5 -- License     :  BSD-style (see the file libraries/base/LICENSE)
6 -- 
7 -- Maintainer  :  libraries@haskell.org
8 -- Stability   :  provisional
9 -- Portability :  portable
10 --
11 -- John Hughes\'s and Simon Peyton Jones\'s Pretty Printer Combinators
12 -- 
13 -- Based on /The Design of a Pretty-printing Library/
14 -- in Advanced Functional Programming,
15 -- Johan Jeuring and Erik Meijer (eds), LNCS 925
16 -- <http://www.cs.chalmers.se/~rjmh/Papers/pretty.ps>
17 --
18 -- Heavily modified by Simon Peyton Jones, Dec 96
19 --
20 -----------------------------------------------------------------------------
21
22 {-
23 Version 3.0     28 May 1997
24   * Cured massive performance bug.  If you write
25
26         foldl <> empty (map (text.show) [1..10000])
27
28     you get quadratic behaviour with V2.0.  Why?  For just the same
29     reason as you get quadratic behaviour with left-associated (++)
30     chains.
31
32     This is really bad news.  One thing a pretty-printer abstraction
33     should certainly guarantee is insensivity to associativity.  It
34     matters: suddenly GHC's compilation times went up by a factor of
35     100 when I switched to the new pretty printer.
36
37     I fixed it with a bit of a hack (because I wanted to get GHC back
38     on the road).  I added two new constructors to the Doc type, Above
39     and Beside:
40
41          <> = Beside
42          $$ = Above
43
44     Then, where I need to get to a "TextBeside" or "NilAbove" form I
45     "force" the Doc to squeeze out these suspended calls to Beside and
46     Above; but in so doing I re-associate. It's quite simple, but I'm
47     not satisfied that I've done the best possible job.  I'll send you
48     the code if you are interested.
49
50   * Added new exports:
51         punctuate, hang
52         int, integer, float, double, rational,
53         lparen, rparen, lbrack, rbrack, lbrace, rbrace,
54
55   * fullRender's type signature has changed.  Rather than producing a
56     string it now takes an extra couple of arguments that tells it how
57     to glue fragments of output together:
58
59         fullRender :: Mode
60                    -> Int                       -- Line length
61                    -> Float                     -- Ribbons per line
62                    -> (TextDetails -> a -> a)   -- What to do with text
63                    -> a                         -- What to do at the end
64                    -> Doc
65                    -> a                         -- Result
66
67     The "fragments" are encapsulated in the TextDetails data type:
68
69         data TextDetails = Chr  Char
70                          | Str  String
71                          | PStr FAST_STRING
72
73     The Chr and Str constructors are obvious enough.  The PStr
74     constructor has a packed string (FAST_STRING) inside it.  It's
75     generated by using the new "ptext" export.
76
77     An advantage of this new setup is that you can get the renderer to
78     do output directly (by passing in a function of type (TextDetails
79     -> IO () -> IO ()), rather than producing a string that you then
80     print.
81
82
83 Version 2.0     24 April 1997
84   * Made empty into a left unit for <> as well as a right unit;
85     it is also now true that
86         nest k empty = empty
87     which wasn't true before.
88
89   * Fixed an obscure bug in sep that occassionally gave very wierd behaviour
90
91   * Added $+$
92
93   * Corrected and tidied up the laws and invariants
94
95 ======================================================================
96 Relative to John's original paper, there are the following new features:
97
98 1.  There's an empty document, "empty".  It's a left and right unit for 
99     both <> and $$, and anywhere in the argument list for
100     sep, hcat, hsep, vcat, fcat etc.
101
102     It is Really Useful in practice.
103
104 2.  There is a paragraph-fill combinator, fsep, that's much like sep,
105     only it keeps fitting things on one line until itc can't fit any more.
106
107 3.  Some random useful extra combinators are provided.  
108         <+> puts its arguments beside each other with a space between them,
109             unless either argument is empty in which case it returns the other
110
111
112         hcat is a list version of <>
113         hsep is a list version of <+>
114         vcat is a list version of $$
115
116         sep (separate) is either like hsep or like vcat, depending on what fits
117
118         cat  is behaves like sep,  but it uses <> for horizontal conposition
119         fcat is behaves like fsep, but it uses <> for horizontal conposition
120
121         These new ones do the obvious things:
122                 char, semi, comma, colon, space,
123                 parens, brackets, braces, 
124                 quotes, doubleQuotes
125
126 4.  The "above" combinator, $$, now overlaps its two arguments if the
127     last line of the top argument stops before the first line of the
128     second begins.
129
130         For example:  text "hi" $$ nest 5 "there"
131         lays out as
132                         hi   there
133         rather than
134                         hi
135                              there
136
137         There are two places this is really useful
138
139         a) When making labelled blocks, like this:
140                 Left ->   code for left
141                 Right ->  code for right
142                 LongLongLongLabel ->
143                           code for longlonglonglabel
144            The block is on the same line as the label if the label is
145            short, but on the next line otherwise.
146
147         b) When laying out lists like this:
148                 [ first
149                 , second
150                 , third
151                 ]
152            which some people like.  But if the list fits on one line
153            you want [first, second, third].  You can't do this with
154            John's original combinators, but it's quite easy with the
155            new $$.
156
157         The combinator $+$ gives the original "never-overlap" behaviour.
158
159 5.      Several different renderers are provided:
160                 * a standard one
161                 * one that uses cut-marks to avoid deeply-nested documents 
162                         simply piling up in the right-hand margin
163                 * one that ignores indentation (fewer chars output; good for machines)
164                 * one that ignores indentation and newlines (ditto, only more so)
165
166 6.      Numerous implementation tidy-ups
167         Use of unboxed data types to speed up the implementation
168 -}
169
170 module Text.PrettyPrint.HughesPJ (
171         Doc,            -- Abstract
172         Mode(..), TextDetails(..),
173
174         empty, isEmpty, nest,
175
176         text, char, ptext,
177         int, integer, float, double, rational,
178         parens, brackets, braces, quotes, doubleQuotes,
179         semi, comma, colon, space, equals,
180         lparen, rparen, lbrack, rbrack, lbrace, rbrace,
181
182         (<>), (<+>), hcat, hsep, 
183         ($$), ($+$), vcat, 
184         sep, cat, 
185         fsep, fcat, 
186
187         hang, punctuate,
188         
189 --      renderStyle,            -- Haskell 1.3 only
190         render, fullRender
191   ) where
192
193
194 import Prelude
195
196 infixl 6 <> 
197 infixl 6 <+>
198 infixl 5 $$, $+$
199
200 -- ---------------------------------------------------------------------------
201 -- The interface
202
203 -- The primitive Doc values
204
205 empty                     :: Doc
206 isEmpty                   :: Doc    -> Bool
207 text                      :: String -> Doc 
208 char                      :: Char -> Doc
209
210 semi, comma, colon, space, equals              :: Doc
211 lparen, rparen, lbrack, rbrack, lbrace, rbrace :: Doc
212
213 parens, brackets, braces  :: Doc -> Doc 
214 quotes, doubleQuotes      :: Doc -> Doc
215
216 int      :: Int -> Doc
217 integer  :: Integer -> Doc
218 float    :: Float -> Doc
219 double   :: Double -> Doc
220 rational :: Rational -> Doc
221
222
223 -- Combining @Doc@ values
224
225 (<>)   :: Doc -> Doc -> Doc     -- Beside
226 hcat   :: [Doc] -> Doc          -- List version of <>
227 (<+>)  :: Doc -> Doc -> Doc     -- Beside, separated by space
228 hsep   :: [Doc] -> Doc          -- List version of <+>
229
230 ($$)   :: Doc -> Doc -> Doc     -- Above; if there is no
231                                 -- overlap it "dovetails" the two
232 vcat   :: [Doc] -> Doc          -- List version of $$
233
234 cat    :: [Doc] -> Doc          -- Either hcat or vcat
235 sep    :: [Doc] -> Doc          -- Either hsep or vcat
236 fcat   :: [Doc] -> Doc          -- ``Paragraph fill'' version of cat
237 fsep   :: [Doc] -> Doc          -- ``Paragraph fill'' version of sep
238
239 nest   :: Int -> Doc -> Doc     -- Nested
240
241
242 -- GHC-specific ones.
243
244 hang :: Doc -> Int -> Doc -> Doc
245 punctuate :: Doc -> [Doc] -> [Doc]      -- punctuate p [d1, ... dn] = [d1 <> p, d2 <> p, ... dn-1 <> p, dn]
246
247
248 -- Displaying @Doc@ values. 
249
250 instance Show Doc where
251   showsPrec prec doc cont = showDoc doc cont
252
253 render     :: Doc -> String             -- Uses default style
254 fullRender :: Mode
255            -> Int                       -- Line length
256            -> Float                     -- Ribbons per line
257            -> (TextDetails -> a -> a)   -- What to do with text
258            -> a                         -- What to do at the end
259            -> Doc
260            -> a                         -- Result
261
262 {-      When we start using 1.3 
263 renderStyle  :: Style -> Doc -> String
264 data Style = Style { lineLength     :: Int,     -- In chars
265                      ribbonsPerLine :: Float,   -- Ratio of ribbon length to line length
266                      mode :: Mode
267              }
268 style :: Style          -- The default style
269 style = Style { lineLength = 100, ribbonsPerLine = 2.5, mode = PageMode }
270 -}
271
272 data Mode = PageMode            -- Normal 
273           | ZigZagMode          -- With zig-zag cuts
274           | LeftMode            -- No indentation, infinitely long lines
275           | OneLineMode         -- All on one line
276
277
278 -- ---------------------------------------------------------------------------
279 -- The Doc calculus
280
281 -- The Doc combinators satisfy the following laws:
282
283 {-
284 Laws for $$
285 ~~~~~~~~~~~
286 <a1>    (x $$ y) $$ z   = x $$ (y $$ z)
287 <a2>    empty $$ x      = x
288 <a3>    x $$ empty      = x
289
290         ...ditto $+$...
291
292 Laws for <>
293 ~~~~~~~~~~~
294 <b1>    (x <> y) <> z   = x <> (y <> z)
295 <b2>    empty <> x      = empty
296 <b3>    x <> empty      = x
297
298         ...ditto <+>...
299
300 Laws for text
301 ~~~~~~~~~~~~~
302 <t1>    text s <> text t        = text (s++t)
303 <t2>    text "" <> x            = x, if x non-empty
304
305 Laws for nest
306 ~~~~~~~~~~~~~
307 <n1>    nest 0 x                = x
308 <n2>    nest k (nest k' x)      = nest (k+k') x
309 <n3>    nest k (x <> y)         = nest k z <> nest k y
310 <n4>    nest k (x $$ y)         = nest k x $$ nest k y
311 <n5>    nest k empty            = empty
312 <n6>    x <> nest k y           = x <> y, if x non-empty
313
314 ** Note the side condition on <n6>!  It is this that
315 ** makes it OK for empty to be a left unit for <>.
316
317 Miscellaneous
318 ~~~~~~~~~~~~~
319 <m1>    (text s <> x) $$ y = text s <> ((text "" <> x)) $$ 
320                                          nest (-length s) y)
321
322 <m2>    (x $$ y) <> z = x $$ (y <> z)
323         if y non-empty
324
325
326 Laws for list versions
327 ~~~~~~~~~~~~~~~~~~~~~~
328 <l1>    sep (ps++[empty]++qs)   = sep (ps ++ qs)
329         ...ditto hsep, hcat, vcat, fill...
330
331 <l2>    nest k (sep ps) = sep (map (nest k) ps)
332         ...ditto hsep, hcat, vcat, fill...
333
334 Laws for oneLiner
335 ~~~~~~~~~~~~~~~~~
336 <o1>    oneLiner (nest k p) = nest k (oneLiner p)
337 <o2>    oneLiner (x <> y)   = oneLiner x <> oneLiner y 
338
339 You might think that the following verion of <m1> would
340 be neater:
341
342 <3 NO>  (text s <> x) $$ y = text s <> ((empty <> x)) $$ 
343                                          nest (-length s) y)
344
345 But it doesn't work, for if x=empty, we would have
346
347         text s $$ y = text s <> (empty $$ nest (-length s) y)
348                     = text s <> nest (-length s) y
349 -}
350
351 -- ---------------------------------------------------------------------------
352 -- Simple derived definitions
353
354 semi  = char ';'
355 colon = char ':'
356 comma = char ','
357 space = char ' '
358 equals = char '='
359 lparen = char '('
360 rparen = char ')'
361 lbrack = char '['
362 rbrack = char ']'
363 lbrace = char '{'
364 rbrace = char '}'
365
366 int      n = text (show n)
367 integer  n = text (show n)
368 float    n = text (show n)
369 double   n = text (show n)
370 rational n = text (show n)
371 -- SIGBJORN wrote instead:
372 -- rational n = text (show (fromRationalX n))
373
374 quotes p        = char '`' <> p <> char '\''
375 doubleQuotes p  = char '"' <> p <> char '"'
376 parens p        = char '(' <> p <> char ')'
377 brackets p      = char '[' <> p <> char ']'
378 braces p        = char '{' <> p <> char '}'
379
380
381 hcat = foldr (<>)  empty
382 hsep = foldr (<+>) empty
383 vcat = foldr ($$)  empty
384
385 hang d1 n d2 = sep [d1, nest n d2]
386
387 punctuate p []     = []
388 punctuate p (d:ds) = go d ds
389                    where
390                      go d [] = [d]
391                      go d (e:es) = (d <> p) : go e es
392
393 -- ---------------------------------------------------------------------------
394 -- The Doc data type
395
396 -- A Doc represents a *set* of layouts.  A Doc with
397 -- no occurrences of Union or NoDoc represents just one layout.
398
399 data Doc
400  = Empty                                -- empty
401  | NilAbove Doc                         -- text "" $$ x
402  | TextBeside TextDetails !Int Doc      -- text s <> x  
403  | Nest !Int Doc                        -- nest k x
404  | Union Doc Doc                        -- ul `union` ur
405  | NoDoc                                -- The empty set of documents
406  | Beside Doc Bool Doc                  -- True <=> space between
407  | Above  Doc Bool Doc                  -- True <=> never overlap
408
409 type RDoc = Doc         -- RDoc is a "reduced Doc", guaranteed not to have a top-level Above or Beside
410
411
412 reduceDoc :: Doc -> RDoc
413 reduceDoc (Beside p g q) = beside p g (reduceDoc q)
414 reduceDoc (Above  p g q) = above  p g (reduceDoc q)
415 reduceDoc p              = p
416
417
418 data TextDetails = Chr  Char
419                  | Str  String
420                  | PStr String
421 space_text = Chr ' '
422 nl_text    = Chr '\n'
423
424 {-
425   Here are the invariants:
426   
427   * The argument of NilAbove is never Empty. Therefore
428     a NilAbove occupies at least two lines.
429   
430   * The arugment of @TextBeside@ is never @Nest@.
431   
432   
433   * The layouts of the two arguments of @Union@ both flatten to the same 
434     string.
435   
436   * The arguments of @Union@ are either @TextBeside@, or @NilAbove@.
437   
438   * The right argument of a union cannot be equivalent to the empty set
439     (@NoDoc@).  If the left argument of a union is equivalent to the
440     empty set (@NoDoc@), then the @NoDoc@ appears in the first line.
441   
442   * An empty document is always represented by @Empty@.  It can't be
443     hidden inside a @Nest@, or a @Union@ of two @Empty@s.
444   
445   * The first line of every layout in the left argument of @Union@ is
446     longer than the first line of any layout in the right argument.
447     (1) ensures that the left argument has a first line.  In view of
448     (3), this invariant means that the right argument must have at
449     least two lines.
450 -}
451
452         -- Arg of a NilAbove is always an RDoc
453 nilAbove_ p = NilAbove p
454
455         -- Arg of a TextBeside is always an RDoc
456 textBeside_ s sl p = TextBeside s sl p
457
458         -- Arg of Nest is always an RDoc
459 nest_ k p = Nest k p
460
461         -- Args of union are always RDocs
462 union_ p q = Union p q
463
464
465 -- Notice the difference between
466 --         * NoDoc (no documents)
467 --         * Empty (one empty document; no height and no width)
468 --         * text "" (a document containing the empty string;
469 --                    one line high, but has no width)
470
471
472 -- ---------------------------------------------------------------------------
473 -- @empty@, @text@, @nest@, @union@
474
475 empty = Empty
476
477 isEmpty Empty = True
478 isEmpty _     = False
479
480 char  c = textBeside_ (Chr c) 1 Empty
481 text  s = case length   s of {sl -> textBeside_ (Str s)  sl Empty}
482 ptext s = case length s of {sl -> textBeside_ (PStr s) sl Empty}
483
484 nest k  p = mkNest k (reduceDoc p)        -- Externally callable version
485
486 -- mkNest checks for Nest's invariant that it doesn't have an Empty inside it
487 mkNest k       _           | k `seq` False = undefined
488 mkNest k       (Nest k1 p) = mkNest (k + k1) p
489 mkNest k       NoDoc       = NoDoc
490 mkNest k       Empty       = Empty
491 mkNest 0       p           = p                  -- Worth a try!
492 mkNest k       p           = nest_ k p
493
494 -- mkUnion checks for an empty document
495 mkUnion Empty q = Empty
496 mkUnion p q     = p `union_` q
497
498 -- ---------------------------------------------------------------------------
499 -- Vertical composition @$$@
500
501 p $$  q = Above p False q
502 p $+$ q = Above p True q
503
504 above :: Doc -> Bool -> RDoc -> RDoc
505 above (Above p g1 q1)  g2 q2 = above p g1 (above q1 g2 q2)
506 above p@(Beside _ _ _) g  q  = aboveNest (reduceDoc p) g 0 (reduceDoc q)
507 above p g q                  = aboveNest p             g 0 (reduceDoc q)
508
509 aboveNest :: RDoc -> Bool -> Int -> RDoc -> RDoc
510 -- Specfication: aboveNest p g k q = p $g$ (nest k q)
511
512 aboveNest _                   _ k _ | k `seq` False = undefined
513 aboveNest NoDoc               g k q = NoDoc
514 aboveNest (p1 `Union` p2)     g k q = aboveNest p1 g k q `union_` 
515                                       aboveNest p2 g k q
516                                 
517 aboveNest Empty               g k q = mkNest k q
518 aboveNest (Nest k1 p)         g k q = nest_ k1 (aboveNest p g (k - k1) q)
519                                   -- p can't be Empty, so no need for mkNest
520                                 
521 aboveNest (NilAbove p)        g k q = nilAbove_ (aboveNest p g k q)
522 aboveNest (TextBeside s sl p) g k q = k1 `seq` textBeside_ s sl rest
523                                     where
524                                       k1   = k - sl
525                                       rest = case p of
526                                                 Empty -> nilAboveNest g k1 q
527                                                 other -> aboveNest  p g k1 q
528
529
530 nilAboveNest :: Bool -> Int -> RDoc -> RDoc
531 -- Specification: text s <> nilaboveNest g k q 
532 --              = text s <> (text "" $g$ nest k q)
533
534 nilAboveNest _ k _           | k `seq` False = undefined
535 nilAboveNest g k Empty       = Empty    -- Here's why the "text s <>" is in the spec!
536 nilAboveNest g k (Nest k1 q) = nilAboveNest g (k + k1) q
537
538 nilAboveNest g k q           | (not g) && (k > 0)        -- No newline if no overlap
539                              = textBeside_ (Str (spaces k)) k q
540                              | otherwise                        -- Put them really above
541                              = nilAbove_ (mkNest k q)
542
543 -- ---------------------------------------------------------------------------
544 -- Horizontal composition @<>@
545
546 p <>  q = Beside p False q
547 p <+> q = Beside p True  q
548
549 beside :: Doc -> Bool -> RDoc -> RDoc
550 -- Specification: beside g p q = p <g> q
551  
552 beside NoDoc               g q   = NoDoc
553 beside (p1 `Union` p2)     g q   = (beside p1 g q) `union_` (beside p2 g q)
554 beside Empty               g q   = q
555 beside (Nest k p)          g q   = nest_ k (beside p g q)       -- p non-empty
556 beside p@(Beside p1 g1 q1) g2 q2 
557            {- (A `op1` B) `op2` C == A `op1` (B `op2` C)  iff op1 == op2 
558                                                  [ && (op1 == <> || op1 == <+>) ] -}
559          | g1 == g2              = beside p1 g1 (beside q1 g2 q2)
560          | otherwise             = beside (reduceDoc p) g2 q2
561 beside p@(Above _ _ _)     g q   = beside (reduceDoc p) g q
562 beside (NilAbove p)        g q   = nilAbove_ (beside p g q)
563 beside (TextBeside s sl p) g q   = textBeside_ s sl rest
564                                where
565                                   rest = case p of
566                                            Empty -> nilBeside g q
567                                            other -> beside p g q
568
569
570 nilBeside :: Bool -> RDoc -> RDoc
571 -- Specification: text "" <> nilBeside g p 
572 --              = text "" <g> p
573
574 nilBeside g Empty      = Empty  -- Hence the text "" in the spec
575 nilBeside g (Nest _ p) = nilBeside g p
576 nilBeside g p          | g         = textBeside_ space_text 1 p
577                        | otherwise = p
578
579 -- ---------------------------------------------------------------------------
580 -- Separate, @sep@, Hughes version
581
582 -- Specification: sep ps  = oneLiner (hsep ps)
583 --                         `union`
584 --                          vcat ps
585
586 sep = sepX True         -- Separate with spaces
587 cat = sepX False        -- Don't
588
589 sepX x []     = empty
590 sepX x (p:ps) = sep1 x (reduceDoc p) 0 ps
591
592
593 -- Specification: sep1 g k ys = sep (x : map (nest k) ys)
594 --                            = oneLiner (x <g> nest k (hsep ys))
595 --                              `union` x $$ nest k (vcat ys)
596
597 sep1 :: Bool -> RDoc -> Int -> [Doc] -> RDoc
598 sep1 g _                   k ys | k `seq` False = undefined
599 sep1 g NoDoc               k ys = NoDoc
600 sep1 g (p `Union` q)       k ys = sep1 g p k ys
601                                   `union_`
602                                   (aboveNest q False k (reduceDoc (vcat ys)))
603
604 sep1 g Empty               k ys = mkNest k (sepX g ys)
605 sep1 g (Nest n p)          k ys = nest_ n (sep1 g p (k - n) ys)
606
607 sep1 g (NilAbove p)        k ys = nilAbove_ (aboveNest p False k (reduceDoc (vcat ys)))
608 sep1 g (TextBeside s sl p) k ys = textBeside_ s sl (sepNB g p (k - sl) ys)
609
610 -- Specification: sepNB p k ys = sep1 (text "" <> p) k ys
611 -- Called when we have already found some text in the first item
612 -- We have to eat up nests
613
614 sepNB g (Nest _ p)  k ys  = sepNB g p k ys
615
616 sepNB g Empty k ys        = oneLiner (nilBeside g (reduceDoc rest))
617                                 `mkUnion` 
618                             nilAboveNest False k (reduceDoc (vcat ys))
619                           where
620                             rest | g         = hsep ys
621                                  | otherwise = hcat ys
622
623 sepNB g p k ys            = sep1 g p k ys
624
625 -- ---------------------------------------------------------------------------
626 -- @fill@
627
628 fsep = fill True
629 fcat = fill False
630
631 -- Specification: 
632 --   fill []  = empty
633 --   fill [p] = p
634 --   fill (p1:p2:ps) = oneLiner p1 <#> nest (length p1) 
635 --                                          (fill (oneLiner p2 : ps))
636 --                     `union`
637 --                      p1 $$ fill ps
638
639 fill g []     = empty
640 fill g (p:ps) = fill1 g (reduceDoc p) 0 ps
641
642
643 fill1 :: Bool -> RDoc -> Int -> [Doc] -> Doc
644 fill1 g _                   k ys | k `seq` False = undefined
645 fill1 g NoDoc               k ys = NoDoc
646 fill1 g (p `Union` q)       k ys = fill1 g p k ys
647                                    `union_`
648                                    (aboveNest q False k (fill g ys))
649
650 fill1 g Empty               k ys = mkNest k (fill g ys)
651 fill1 g (Nest n p)          k ys = nest_ n (fill1 g p (k - n) ys)
652
653 fill1 g (NilAbove p)        k ys = nilAbove_ (aboveNest p False k (fill g ys))
654 fill1 g (TextBeside s sl p) k ys = textBeside_ s sl (fillNB g p (k - sl) ys)
655
656 fillNB g _           k ys | k `seq` False = undefined
657 fillNB g (Nest _ p)  k ys  = fillNB g p k ys
658 fillNB g Empty k []        = Empty
659 fillNB g Empty k (y:ys)    = nilBeside g (fill1 g (oneLiner (reduceDoc y)) k1 ys)
660                              `mkUnion` 
661                              nilAboveNest False k (fill g (y:ys))
662                            where
663                              k1 | g         = k - 1
664                                 | otherwise = k
665
666 fillNB g p k ys            = fill1 g p k ys
667
668
669 -- ---------------------------------------------------------------------------
670 -- Selecting the best layout
671
672 best :: Mode
673      -> Int             -- Line length
674      -> Int             -- Ribbon length
675      -> RDoc
676      -> RDoc            -- No unions in here!
677
678 best OneLineMode w r p
679   = get p
680   where
681     get Empty               = Empty
682     get NoDoc               = NoDoc
683     get (NilAbove p)        = nilAbove_ (get p)
684     get (TextBeside s sl p) = textBeside_ s sl (get p)
685     get (Nest k p)          = get p             -- Elide nest
686     get (p `Union` q)       = first (get p) (get q)
687
688 best mode w r p
689   = get w p
690   where
691     get :: Int          -- (Remaining) width of line
692         -> Doc -> Doc
693     get w _ | w==0 && False   = undefined
694     get w Empty               = Empty
695     get w NoDoc               = NoDoc
696     get w (NilAbove p)        = nilAbove_ (get w p)
697     get w (TextBeside s sl p) = textBeside_ s sl (get1 w sl p)
698     get w (Nest k p)          = nest_ k (get (w - k) p)
699     get w (p `Union` q)       = nicest w r (get w p) (get w q)
700
701     get1 :: Int         -- (Remaining) width of line
702          -> Int         -- Amount of first line already eaten up
703          -> Doc         -- This is an argument to TextBeside => eat Nests
704          -> Doc         -- No unions in here!
705
706     get1 w _ _ | w==0 && False = undefined
707     get1 w sl Empty               = Empty
708     get1 w sl NoDoc               = NoDoc
709     get1 w sl (NilAbove p)        = nilAbove_ (get (w - sl) p)
710     get1 w sl (TextBeside t tl p) = textBeside_ t tl (get1 w (sl + tl) p)
711     get1 w sl (Nest k p)          = get1 w sl p
712     get1 w sl (p `Union` q)       = nicest1 w r sl (get1 w sl p) 
713                                                    (get1 w sl q)
714
715 nicest w r p q = nicest1 w r 0 p q
716 nicest1 w r sl p q | fits ((w `minn` r) - sl) p = p
717                    | otherwise                   = q
718
719 fits :: Int     -- Space available
720      -> Doc
721      -> Bool    -- True if *first line* of Doc fits in space available
722  
723 fits n p    | n < 0 = False
724 fits n NoDoc               = False
725 fits n Empty               = True
726 fits n (NilAbove _)        = True
727 fits n (TextBeside _ sl p) = fits (n - sl) p
728
729 minn x y | x < y    = x
730          | otherwise = y
731
732 -- @first@ and @nonEmptySet@ are similar to @nicest@ and @fits@, only simpler.
733 -- @first@ returns its first argument if it is non-empty, otherwise its second.
734
735 first p q | nonEmptySet p = p 
736           | otherwise     = q
737
738 nonEmptySet NoDoc           = False
739 nonEmptySet (p `Union` q)      = True
740 nonEmptySet Empty              = True
741 nonEmptySet (NilAbove p)       = True           -- NoDoc always in first line
742 nonEmptySet (TextBeside _ _ p) = nonEmptySet p
743 nonEmptySet (Nest _ p)         = nonEmptySet p
744
745 -- @oneLiner@ returns the one-line members of the given set of @Doc@s.
746
747 oneLiner :: Doc -> Doc
748 oneLiner NoDoc               = NoDoc
749 oneLiner Empty               = Empty
750 oneLiner (NilAbove p)        = NoDoc
751 oneLiner (TextBeside s sl p) = textBeside_ s sl (oneLiner p)
752 oneLiner (Nest k p)          = nest_ k (oneLiner p)
753 oneLiner (p `Union` q)       = oneLiner p
754
755
756 -- ---------------------------------------------------------------------------
757 -- Displaying the best layout
758
759 {-
760 renderStyle Style{mode, lineLength, ribbonsPerLine} doc 
761   = fullRender mode lineLength ribbonsPerLine doc ""
762 -}
763
764 render doc       = showDoc doc ""
765 showDoc doc rest = fullRender PageMode 100 1.5 string_txt rest doc
766
767 string_txt (Chr c)   s  = c:s
768 string_txt (Str s1)  s2 = s1 ++ s2
769 string_txt (PStr s1) s2 = s1 ++ s2
770
771
772 fullRender OneLineMode _ _ txt end doc = easy_display space_text txt end (reduceDoc doc)
773 fullRender LeftMode    _ _ txt end doc = easy_display nl_text    txt end (reduceDoc doc)
774
775 fullRender mode line_length ribbons_per_line txt end doc
776   = display mode line_length ribbon_length txt end best_doc
777   where 
778     best_doc = best mode hacked_line_length ribbon_length (reduceDoc doc)
779
780     hacked_line_length, ribbon_length :: Int
781     ribbon_length = round (fromIntegral line_length / ribbons_per_line)
782     hacked_line_length = case mode of { ZigZagMode -> maxBound; other -> line_length }
783
784 display mode page_width ribbon_width txt end doc
785   = case page_width - ribbon_width of { gap_width ->
786     case gap_width `quot` 2 of { shift ->
787     let
788         lay k _            | k `seq` False = undefined
789         lay k (Nest k1 p)  = lay (k + k1) p
790         lay k Empty        = end
791     
792         lay k (NilAbove p) = nl_text `txt` lay k p
793     
794         lay k (TextBeside s sl p)
795             = case mode of
796                     ZigZagMode |  k >= gap_width
797                                -> nl_text `txt` (
798                                   Str (multi_ch shift '/') `txt` (
799                                   nl_text `txt` (
800                                   lay1 (k - shift) s sl p)))
801
802                                |  k < 0
803                                -> nl_text `txt` (
804                                   Str (multi_ch shift '\\') `txt` (
805                                   nl_text `txt` (
806                                   lay1 (k + shift) s sl p )))
807
808                     other -> lay1 k s sl p
809     
810         lay1 k _ sl _ | k+sl `seq` False = undefined
811         lay1 k s sl p = Str (indent k) `txt` (s `txt` lay2 (k + sl) p)
812     
813         lay2 k _ | k `seq` False = undefined
814         lay2 k (NilAbove p)        = nl_text `txt` lay k p
815         lay2 k (TextBeside s sl p) = s `txt` (lay2 (k + sl) p)
816         lay2 k (Nest _ p)          = lay2 k p
817         lay2 k Empty               = end
818     in
819     lay 0 doc
820     }}
821
822 cant_fail = error "easy_display: NoDoc"
823 easy_display nl_text txt end doc 
824   = lay doc cant_fail
825   where
826     lay NoDoc               no_doc = no_doc
827     lay (Union p q)         no_doc = {- lay p -} (lay q cant_fail)              -- Second arg can't be NoDoc
828     lay (Nest k p)          no_doc = lay p no_doc
829     lay Empty               no_doc = end
830     lay (NilAbove p)        no_doc = nl_text `txt` lay p cant_fail      -- NoDoc always on first line
831     lay (TextBeside s sl p) no_doc = s `txt` lay p no_doc
832
833 indent n | n >= 8 = '\t' : indent (n - 8)
834          | otherwise      = spaces n
835
836 multi_ch 0 ch = ""
837 multi_ch n       ch = ch : multi_ch (n - 1) ch
838
839 spaces 0 = ""
840 spaces n       = ' ' : spaces (n - 1)
841