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