Make some profiling flags dynamic
[ghc-hetmet.git] / 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 FastString
59
60     The Chr and Str constructors are obvious enough.  The PStr constructor has a packed
61     string (FastString) 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 it 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 {-# OPTIONS -fno-warn-unused-imports #-}
156 -- XXX GHC 6.9 seems to be confused by unpackCString# being used only in
157 --     a RULE
158
159 module Pretty (
160         Doc,            -- Abstract
161         Mode(..), TextDetails(..),
162
163         empty, isEmpty, nest,
164
165         char, text, ftext, ptext,
166         int, integer, float, double, rational,
167         parens, brackets, braces, quotes, doubleQuotes,
168         semi, comma, colon, space, equals,
169         lparen, rparen, lbrack, rbrack, lbrace, rbrace, cparen,
170
171         (<>), (<+>), hcat, hsep,
172         ($$), ($+$), vcat,
173         sep, cat,
174         fsep, fcat,
175
176         hang, punctuate,
177
178 --      renderStyle,            -- Haskell 1.3 only
179         render, fullRender, printDoc, showDocWith
180   ) where
181
182 import BufWrite
183 import FastString
184 import FastTypes
185 import Panic
186
187 import Numeric (fromRat)
188 import System.IO
189 --import Foreign.Ptr (castPtr)
190
191 #if defined(__GLASGOW_HASKELL__)
192 --for a RULES
193 import GHC.Base ( unpackCString# )
194 import GHC.Exts ( Int# )
195 import GHC.Ptr  ( Ptr(..) )
196 #endif
197
198 -- Don't import Util( assertPanic ) because it makes a loop in the module structure
199
200 infixl 6 <>
201 infixl 6 <+>
202 infixl 5 $$, $+$
203 \end{code}
204
205
206 \begin{code}
207
208 -- Disable ASSERT checks; they are expensive!
209 #define LOCAL_ASSERT(x)
210
211 \end{code}
212
213
214 %*********************************************************
215 %*                                                       *
216 \subsection{The interface}
217 %*                                                       *
218 %*********************************************************
219
220 The primitive @Doc@ values
221
222 \begin{code}
223 empty                     :: Doc
224 isEmpty                   :: Doc    -> Bool
225 text                      :: String -> Doc
226 char                      :: Char -> Doc
227
228 semi, comma, colon, space, equals              :: Doc
229 lparen, rparen, lbrack, rbrack, lbrace, rbrace :: Doc
230
231 parens, brackets, braces  :: Doc -> Doc
232 quotes, doubleQuotes      :: Doc -> Doc
233
234 int      :: Int -> Doc
235 integer  :: Integer -> Doc
236 float    :: Float -> Doc
237 double   :: Double -> Doc
238 rational :: Rational -> Doc
239 \end{code}
240
241 Combining @Doc@ values
242
243 \begin{code}
244 (<>)   :: Doc -> Doc -> Doc     -- Beside
245 hcat   :: [Doc] -> Doc          -- List version of <>
246 (<+>)  :: Doc -> Doc -> Doc     -- Beside, separated by space
247 hsep   :: [Doc] -> Doc          -- List version of <+>
248
249 ($$)   :: Doc -> Doc -> Doc     -- Above; if there is no
250                                 -- overlap it "dovetails" the two
251 vcat   :: [Doc] -> Doc          -- List version of $$
252
253 cat    :: [Doc] -> Doc          -- Either hcat or vcat
254 sep    :: [Doc] -> Doc          -- Either hsep or vcat
255 fcat   :: [Doc] -> Doc          -- ``Paragraph fill'' version of cat
256 fsep   :: [Doc] -> Doc          -- ``Paragraph fill'' version of sep
257
258 nest   :: Int -> Doc -> Doc     -- Nested
259 \end{code}
260
261 GHC-specific ones.
262
263 \begin{code}
264 hang :: Doc -> Int -> Doc -> Doc
265 punctuate :: Doc -> [Doc] -> [Doc]      -- punctuate p [d1, ... dn] = [d1 <> p, d2 <> p, ... dn-1 <> p, dn]
266 \end{code}
267
268 Displaying @Doc@ values.
269
270 \begin{code}
271 instance Show Doc where
272   showsPrec _ doc cont = showDoc doc cont
273
274 render     :: Doc -> String             -- Uses default style
275 fullRender :: Mode
276            -> Int                       -- Line length
277            -> Float                     -- Ribbons per line
278            -> (TextDetails -> a -> a)   -- What to do with text
279            -> a                         -- What to do at the end
280            -> Doc
281            -> a                         -- Result
282
283 {-      When we start using 1.3
284 renderStyle  :: Style -> Doc -> String
285 data Style = Style { lineLength     :: Int,     -- In chars
286                      ribbonsPerLine :: Float,   -- Ratio of ribbon length to line length
287                      mode :: Mode
288              }
289 style :: Style          -- The default style
290 style = Style { lineLength = 100, ribbonsPerLine = 2.5, mode = PageMode }
291 -}
292
293 data Mode = PageMode            -- Normal
294           | ZigZagMode          -- With zig-zag cuts
295           | LeftMode            -- No indentation, infinitely long lines
296           | OneLineMode         -- All on one line
297
298 \end{code}
299
300
301 %*********************************************************
302 %*                                                       *
303 \subsection{The @Doc@ calculus}
304 %*                                                       *
305 %*********************************************************
306
307 The @Doc@ combinators satisfy the following laws:
308 \begin{verbatim}
309 Laws for $$
310 ~~~~~~~~~~~
311 <a1>    (x $$ y) $$ z   = x $$ (y $$ z)
312 <a2>    empty $$ x      = x
313 <a3>    x $$ empty      = x
314
315         ...ditto $+$...
316
317 Laws for <>
318 ~~~~~~~~~~~
319 <b1>    (x <> y) <> z   = x <> (y <> z)
320 <b2>    empty <> x      = empty
321 <b3>    x <> empty      = x
322
323         ...ditto <+>...
324
325 Laws for text
326 ~~~~~~~~~~~~~
327 <t1>    text s <> text t        = text (s++t)
328 <t2>    text "" <> x            = x, if x non-empty
329
330 Laws for nest
331 ~~~~~~~~~~~~~
332 <n1>    nest 0 x                = x
333 <n2>    nest k (nest k' x)      = nest (k+k') x
334 <n3>    nest k (x <> y)         = nest k z <> nest k y
335 <n4>    nest k (x $$ y)         = nest k x $$ nest k y
336 <n5>    nest k empty            = empty
337 <n6>    x <> nest k y           = x <> y, if x non-empty
338
339  - Note the side condition on <n6>!  It is this that
340    makes it OK for empty to be a left unit for <>.
341
342 Miscellaneous
343 ~~~~~~~~~~~~~
344 <m1>    (text s <> x) $$ y = text s <> ((text "" <> x)) $$
345                                          nest (-length s) y)
346
347 <m2>    (x $$ y) <> z = x $$ (y <> z)
348         if y non-empty
349
350
351 Laws for list versions
352 ~~~~~~~~~~~~~~~~~~~~~~
353 <l1>    sep (ps++[empty]++qs)   = sep (ps ++ qs)
354         ...ditto hsep, hcat, vcat, fill...
355
356 <l2>    nest k (sep ps) = sep (map (nest k) ps)
357         ...ditto hsep, hcat, vcat, fill...
358
359 Laws for oneLiner
360 ~~~~~~~~~~~~~~~~~
361 <o1>    oneLiner (nest k p) = nest k (oneLiner p)
362 <o2>    oneLiner (x <> y)   = oneLiner x <> oneLiner y
363 \end{verbatim}
364
365
366 You might think that the following verion of <m1> would
367 be neater:
368 \begin{verbatim}
369 <3 NO>  (text s <> x) $$ y = text s <> ((empty <> x)) $$
370                                          nest (-length s) y)
371 \end{verbatim}
372 But it doesn't work, for if x=empty, we would have
373 \begin{verbatim}
374         text s $$ y = text s <> (empty $$ nest (-length s) y)
375                     = text s <> nest (-length s) y
376 \end{verbatim}
377
378
379
380 %*********************************************************
381 %*                                                       *
382 \subsection{Simple derived definitions}
383 %*                                                       *
384 %*********************************************************
385
386 \begin{code}
387 semi  = char ';'
388 colon = char ':'
389 comma = char ','
390 space = char ' '
391 equals = char '='
392 lparen = char '('
393 rparen = char ')'
394 lbrack = char '['
395 rbrack = char ']'
396 lbrace = char '{'
397 rbrace = char '}'
398
399 int      n = text (show n)
400 integer  n = text (show n)
401 float    n = text (show n)
402 double   n = text (show n)
403 rational n = text (show (fromRat n :: Double))
404 --rational n = text (show (fromRationalX n)) -- _showRational 30 n)
405
406 quotes p        = char '`' <> p <> char '\''
407 doubleQuotes p  = char '"' <> p <> char '"'
408 parens p        = char '(' <> p <> char ')'
409 brackets p      = char '[' <> p <> char ']'
410 braces p        = char '{' <> p <> char '}'
411
412 cparen :: Bool -> Doc -> Doc
413 cparen True  = parens
414 cparen False = id
415
416 hcat = foldr (<>)  empty
417 hsep = foldr (<+>) empty
418 vcat = foldr ($$)  empty
419
420 hang d1 n d2 = sep [d1, nest n d2]
421
422 punctuate _ []     = []
423 punctuate p (d:ds) = go d ds
424                    where
425                      go d [] = [d]
426                      go d (e:es) = (d <> p) : go e es
427 \end{code}
428
429
430 %*********************************************************
431 %*                                                       *
432 \subsection{The @Doc@ data type}
433 %*                                                       *
434 %*********************************************************
435
436 A @Doc@ represents a {\em set} of layouts.  A @Doc@ with
437 no occurrences of @Union@ or @NoDoc@ represents just one layout.
438 \begin{code}
439 data Doc
440  = Empty                                -- empty
441  | NilAbove Doc                         -- text "" $$ x
442  | TextBeside !TextDetails FastInt Doc       -- text s <> x
443  | Nest FastInt Doc                         -- nest k x
444  | Union Doc Doc                        -- ul `union` ur
445  | NoDoc                                -- The empty set of documents
446  | Beside Doc Bool Doc                  -- True <=> space between
447  | Above  Doc Bool Doc                  -- True <=> never overlap
448
449 type RDoc = Doc         -- RDoc is a "reduced Doc", guaranteed not to have a top-level Above or Beside
450
451
452 reduceDoc :: Doc -> RDoc
453 reduceDoc (Beside p g q) = beside p g (reduceDoc q)
454 reduceDoc (Above  p g q) = above  p g (reduceDoc q)
455 reduceDoc p              = p
456
457
458 data TextDetails = Chr  {-#UNPACK#-}!Char
459                  | Str  String
460                  | PStr FastString                      -- a hashed string
461                  | LStr {-#UNPACK#-}!LitString FastInt  -- a '\0'-terminated
462                                                         -- array of bytes
463
464 space_text :: TextDetails
465 space_text = Chr ' '
466 nl_text :: TextDetails
467 nl_text    = Chr '\n'
468 \end{code}
469
470 Here are the invariants:
471 \begin{itemize}
472 \item
473 The argument of @NilAbove@ is never @Empty@. Therefore
474 a @NilAbove@ occupies at least two lines.
475
476 \item
477 The arugment of @TextBeside@ is never @Nest@.
478
479 \item
480 The layouts of the two arguments of @Union@ both flatten to the same string.
481
482 \item
483 The arguments of @Union@ are either @TextBeside@, or @NilAbove@.
484
485 \item
486 The right argument of a union cannot be equivalent to the empty set (@NoDoc@).
487 If the left argument of a union is equivalent to the empty set (@NoDoc@),
488 then the @NoDoc@ appears in the first line.
489
490 \item
491 An empty document is always represented by @Empty@.
492 It can't be hidden inside a @Nest@, or a @Union@ of two @Empty@s.
493
494 \item
495 The first line of every layout in the left argument of @Union@
496 is longer than the first line of any layout in the right argument.
497 (1) ensures that the left argument has a first line.  In view of (3),
498 this invariant means that the right argument must have at least two
499 lines.
500 \end{itemize}
501
502 \begin{code}
503 -- Arg of a NilAbove is always an RDoc
504 nilAbove_ :: Doc -> Doc
505 nilAbove_ p = LOCAL_ASSERT( _ok p ) NilAbove p
506             where
507               _ok Empty = False
508               _ok _     = True
509
510 -- Arg of a TextBeside is always an RDoc
511 textBeside_ :: TextDetails -> FastInt -> Doc -> Doc
512 textBeside_ s sl p = TextBeside s sl (LOCAL_ASSERT( _ok p ) p)
513                    where
514                      _ok (Nest _ _) = False
515                      _ok _          = True
516
517 -- Arg of Nest is always an RDoc
518 nest_ :: FastInt -> Doc -> Doc
519 nest_ k p = Nest k (LOCAL_ASSERT( _ok p ) p)
520           where
521             _ok Empty = False
522             _ok _     = True
523
524 -- Args of union are always RDocs
525 union_ :: Doc -> Doc -> Doc
526 union_ p q = Union (LOCAL_ASSERT( _ok p ) p) (LOCAL_ASSERT( _ok q ) q)
527            where
528              _ok (TextBeside _ _ _) = True
529              _ok (NilAbove _)       = True
530              _ok (Union _ _)        = True
531              _ok _                  = False
532 \end{code}
533
534 Notice the difference between
535         * NoDoc (no documents)
536         * Empty (one empty document; no height and no width)
537         * text "" (a document containing the empty string;
538                    one line high, but has no width)
539
540
541
542 %*********************************************************
543 %*                                                       *
544 \subsection{@empty@, @text@, @nest@, @union@}
545 %*                                                       *
546 %*********************************************************
547
548 \begin{code}
549 empty = Empty
550
551 isEmpty Empty = True
552 isEmpty _     = False
553
554 char  c = textBeside_ (Chr c) (_ILIT(1)) Empty
555 text  s = case iUnbox (length   s) of {sl -> textBeside_ (Str s)  sl Empty}
556 ftext :: FastString -> Doc
557 ftext s = case iUnbox (lengthFS s) of {sl -> textBeside_ (PStr s) sl Empty}
558 ptext :: LitString -> Doc
559 ptext s_= case iUnbox (lengthLS s) of {sl -> textBeside_ (LStr s sl) sl Empty}
560   where s = {-castPtr-} s_
561
562 #if defined(__GLASGOW_HASKELL__)
563 -- RULE that turns (text "abc") into (ptext (A# "abc"#)) to avoid the
564 -- intermediate packing/unpacking of the string.
565 {-# RULES
566   "text/str" forall a. text (unpackCString# a) = ptext (Ptr a)
567  #-}
568 #endif
569
570 nest k  p = mkNest (iUnbox k) (reduceDoc p)        -- Externally callable version
571
572 -- mkNest checks for Nest's invariant that it doesn't have an Empty inside it
573 mkNest :: Int# -> Doc -> Doc
574 mkNest k       (Nest k1 p) = mkNest (k +# k1) p
575 mkNest _       NoDoc       = NoDoc
576 mkNest _       Empty       = Empty
577 mkNest k       p  | k ==# _ILIT(0)  = p       -- Worth a try!
578 mkNest k       p           = nest_ k p
579
580 -- mkUnion checks for an empty document
581 mkUnion :: Doc -> Doc -> Doc
582 mkUnion Empty _ = Empty
583 mkUnion p q     = p `union_` q
584 \end{code}
585
586 %*********************************************************
587 %*                                                       *
588 \subsection{Vertical composition @$$@}
589 %*                                                       *
590 %*********************************************************
591
592
593 \begin{code}
594 p $$  q = Above p False q
595 ($+$) :: Doc -> Doc -> Doc
596 p $+$ q = Above p True q
597
598 above :: Doc -> Bool -> RDoc -> RDoc
599 above (Above p g1 q1)  g2 q2 = above p g1 (above q1 g2 q2)
600 above p@(Beside _ _ _) g  q  = aboveNest (reduceDoc p) g (_ILIT(0)) (reduceDoc q)
601 above p g q                  = aboveNest p             g (_ILIT(0)) (reduceDoc q)
602
603 aboveNest :: RDoc -> Bool -> FastInt -> RDoc -> RDoc
604 -- Specfication: aboveNest p g k q = p $g$ (nest k q)
605
606 aboveNest NoDoc               _ _ _ = NoDoc
607 aboveNest (p1 `Union` p2)     g k q = aboveNest p1 g k q `union_`
608                                       aboveNest p2 g k q
609
610 aboveNest Empty               _ k q = mkNest k q
611 aboveNest (Nest k1 p)         g k q = nest_ k1 (aboveNest p g (k -# k1) q)
612                                   -- p can't be Empty, so no need for mkNest
613
614 aboveNest (NilAbove p)        g k q = nilAbove_ (aboveNest p g k q)
615 aboveNest (TextBeside s sl p) g k q = textBeside_ s sl rest
616                                     where
617                                       k1   = k -# sl
618                                       rest = case p of
619                                                 Empty -> nilAboveNest g k1 q
620                                                 _     -> aboveNest  p g k1 q
621 aboveNest _                   _ _ _ = panic "aboveNest: Unhandled case"
622 \end{code}
623
624 \begin{code}
625 nilAboveNest :: Bool -> FastInt -> RDoc -> RDoc
626 -- Specification: text s <> nilaboveNest g k q
627 --              = text s <> (text "" $g$ nest k q)
628
629 nilAboveNest _ _ Empty       = Empty    -- Here's why the "text s <>" is in the spec!
630 nilAboveNest g k (Nest k1 q) = nilAboveNest g (k +# k1) q
631
632 nilAboveNest g k q           | (not g) && (k ># _ILIT(0))        -- No newline if no overlap
633                              = textBeside_ (Str (spaces k)) k q
634                              | otherwise                        -- Put them really above
635                              = nilAbove_ (mkNest k q)
636 \end{code}
637
638
639 %*********************************************************
640 %*                                                       *
641 \subsection{Horizontal composition @<>@}
642 %*                                                       *
643 %*********************************************************
644
645 \begin{code}
646 p <>  q = Beside p False q
647 p <+> q = Beside p True  q
648
649 beside :: Doc -> Bool -> RDoc -> RDoc
650 -- Specification: beside g p q = p <g> q
651
652 beside NoDoc               _ _   = NoDoc
653 beside (p1 `Union` p2)     g q   = (beside p1 g q) `union_` (beside p2 g q)
654 beside Empty               _ q   = q
655 beside (Nest k p)          g q   = nest_ k $! beside p g q       -- p non-empty
656 beside p@(Beside p1 g1 q1) g2 q2
657            {- (A `op1` B) `op2` C == A `op1` (B `op2` C)  iff op1 == op2
658                                                  [ && (op1 == <> || op1 == <+>) ] -}
659          | g1 == g2              = beside p1 g1 $! beside q1 g2 q2
660          | otherwise             = beside (reduceDoc p) g2 q2
661 beside p@(Above _ _ _)     g q   = let d = reduceDoc p in d `seq` beside d g q
662 beside (NilAbove p)        g q   = nilAbove_ $! beside p g q
663 beside (TextBeside s sl p) g q   = textBeside_ s sl $! rest
664                                where
665                                   rest = case p of
666                                            Empty -> nilBeside g q
667                                            _     -> beside p g q
668 \end{code}
669
670 \begin{code}
671 nilBeside :: Bool -> RDoc -> RDoc
672 -- Specification: text "" <> nilBeside g p
673 --              = text "" <g> p
674
675 nilBeside _ Empty      = Empty  -- Hence the text "" in the spec
676 nilBeside g (Nest _ p) = nilBeside g p
677 nilBeside g p          | g         = textBeside_ space_text (_ILIT(1)) p
678                        | otherwise = p
679 \end{code}
680
681 %*********************************************************
682 %*                                                       *
683 \subsection{Separate, @sep@, Hughes version}
684 %*                                                       *
685 %*********************************************************
686
687 \begin{code}
688 -- Specification: sep ps  = oneLiner (hsep ps)
689 --                         `union`
690 --                          vcat ps
691
692 sep = sepX True         -- Separate with spaces
693 cat = sepX False        -- Don't
694
695 sepX :: Bool -> [Doc] -> Doc
696 sepX _ []     = empty
697 sepX x (p:ps) = sep1 x (reduceDoc p) (_ILIT(0)) ps
698
699
700 -- Specification: sep1 g k ys = sep (x : map (nest k) ys)
701 --                            = oneLiner (x <g> nest k (hsep ys))
702 --                              `union` x $$ nest k (vcat ys)
703
704 sep1 :: Bool -> RDoc -> FastInt -> [Doc] -> RDoc
705 sep1 _ NoDoc               _ _  = NoDoc
706 sep1 g (p `Union` q)       k ys = sep1 g p k ys
707                                   `union_`
708                                   (aboveNest q False k (reduceDoc (vcat ys)))
709
710 sep1 g Empty               k ys = mkNest k (sepX g ys)
711 sep1 g (Nest n p)          k ys = nest_ n (sep1 g p (k -# n) ys)
712
713 sep1 _ (NilAbove p)        k ys = nilAbove_ (aboveNest p False k (reduceDoc (vcat ys)))
714 sep1 g (TextBeside s sl p) k ys = textBeside_ s sl (sepNB g p (k -# sl) ys)
715 sep1 _ _                   _ _  = panic "sep1: Unhandled case"
716
717 -- Specification: sepNB p k ys = sep1 (text "" <> p) k ys
718 -- Called when we have already found some text in the first item
719 -- We have to eat up nests
720
721 sepNB :: Bool -> Doc -> FastInt -> [Doc] -> Doc
722 sepNB g (Nest _ p)  k ys  = sepNB g p k ys
723
724 sepNB g Empty k ys        = oneLiner (nilBeside g (reduceDoc rest))
725                                 `mkUnion`
726                             nilAboveNest False k (reduceDoc (vcat ys))
727                           where
728                             rest | g         = hsep ys
729                                  | otherwise = hcat ys
730
731 sepNB g p k ys            = sep1 g p k ys
732 \end{code}
733
734 %*********************************************************
735 %*                                                       *
736 \subsection{@fill@}
737 %*                                                       *
738 %*********************************************************
739
740 \begin{code}
741 fsep = fill True
742 fcat = fill False
743
744 -- Specification:
745 --   fill []  = empty
746 --   fill [p] = p
747 --   fill (p1:p2:ps) = oneLiner p1 <#> nest (length p1)
748 --                                          (fill (oneLiner p2 : ps))
749 --                     `union`
750 --                      p1 $$ fill ps
751
752 fill :: Bool -> [Doc] -> Doc
753 fill _ []     = empty
754 fill g (p:ps) = fill1 g (reduceDoc p) (_ILIT(0)) ps
755
756
757 fill1 :: Bool -> RDoc -> FastInt -> [Doc] -> Doc
758 fill1 _ NoDoc               _ _  = NoDoc
759 fill1 g (p `Union` q)       k ys = fill1 g p k ys
760                                    `union_`
761                                    (aboveNest q False k (fill g ys))
762
763 fill1 g Empty               k ys = mkNest k (fill g ys)
764 fill1 g (Nest n p)          k ys = nest_ n (fill1 g p (k -# n) ys)
765
766 fill1 g (NilAbove p)        k ys = nilAbove_ (aboveNest p False k (fill g ys))
767 fill1 g (TextBeside s sl p) k ys = textBeside_ s sl (fillNB g p (k -# sl) ys)
768 fill1 _ _                   _ _  = panic "fill1: Unhandled case"
769
770 fillNB :: Bool -> Doc -> Int# -> [Doc] -> Doc
771 fillNB g (Nest _ p)  k ys  = fillNB g p k ys
772 fillNB _ Empty _ []        = Empty
773 fillNB g Empty k (y:ys)    = nilBeside g (fill1 g (oneLiner (reduceDoc y)) k1 ys)
774                              `mkUnion`
775                              nilAboveNest False k (fill g (y:ys))
776                            where
777                              k1 | g         = k -# _ILIT(1)
778                                 | otherwise = k
779
780 fillNB g p k ys            = fill1 g p k ys
781 \end{code}
782
783
784 %*********************************************************
785 %*                                                       *
786 \subsection{Selecting the best layout}
787 %*                                                       *
788 %*********************************************************
789
790 \begin{code}
791 best :: Int             -- Line length
792      -> Int             -- Ribbon length
793      -> RDoc
794      -> RDoc            -- No unions in here!
795
796 best w_ r_ p
797   = get (iUnbox w_) p
798   where
799     r = iUnbox r_
800     get :: FastInt          -- (Remaining) width of line
801         -> Doc -> Doc
802     get _ Empty               = Empty
803     get _ NoDoc               = NoDoc
804     get w (NilAbove p)        = nilAbove_ (get w p)
805     get w (TextBeside s sl p) = textBeside_ s sl (get1 w sl p)
806     get w (Nest k p)          = nest_ k (get (w -# k) p)
807     get w (p `Union` q)       = nicest w r (get w p) (get w q)
808     get _ _                   = panic "best/get: Unhandled case"
809
810     get1 :: FastInt         -- (Remaining) width of line
811          -> FastInt         -- Amount of first line already eaten up
812          -> Doc         -- This is an argument to TextBeside => eat Nests
813          -> Doc         -- No unions in here!
814
815     get1 _ _  Empty               = Empty
816     get1 _ _  NoDoc               = NoDoc
817     get1 w sl (NilAbove p)        = nilAbove_ (get (w -# sl) p)
818     get1 w sl (TextBeside t tl p) = textBeside_ t tl (get1 w (sl +# tl) p)
819     get1 w sl (Nest _ p)          = get1 w sl p
820     get1 w sl (p `Union` q)       = nicest1 w r sl (get1 w sl p)
821                                                    (get1 w sl q)
822     get1 _ _  _                   = panic "best/get1: Unhandled case"
823
824 nicest :: FastInt -> FastInt -> Doc -> Doc -> Doc
825 nicest w r p q = nicest1 w r (_ILIT(0)) p q
826 nicest1 :: FastInt -> FastInt -> Int# -> Doc -> Doc -> Doc
827 nicest1 w r sl p q | fits ((w `minFastInt` r) -# sl) p = p
828                    | otherwise                   = q
829
830 fits :: FastInt     -- Space available
831      -> Doc
832      -> Bool    -- True if *first line* of Doc fits in space available
833
834 fits n _   | n <# _ILIT(0) = False
835 fits _ NoDoc               = False
836 fits _ Empty               = True
837 fits _ (NilAbove _)        = True
838 fits n (TextBeside _ sl p) = fits (n -# sl) p
839 fits _ _                   = panic "fits: Unhandled case"
840 \end{code}
841
842 @first@ and @nonEmptySet@ are similar to @nicest@ and @fits@, only simpler.
843 @first@ returns its first argument if it is non-empty, otherwise its second.
844
845 \begin{code}
846 first :: Doc -> Doc -> Doc
847 first p q | nonEmptySet p = p
848           | otherwise     = q
849
850 nonEmptySet :: Doc -> Bool
851 nonEmptySet NoDoc              = False
852 nonEmptySet (_ `Union` _)      = True
853 nonEmptySet Empty              = True
854 nonEmptySet (NilAbove _)       = True           -- NoDoc always in first line
855 nonEmptySet (TextBeside _ _ p) = nonEmptySet p
856 nonEmptySet (Nest _ p)         = nonEmptySet p
857 nonEmptySet _                  = panic "nonEmptySet: Unhandled case"
858 \end{code}
859
860 @oneLiner@ returns the one-line members of the given set of @Doc@s.
861
862 \begin{code}
863 oneLiner :: Doc -> Doc
864 oneLiner NoDoc               = NoDoc
865 oneLiner Empty               = Empty
866 oneLiner (NilAbove _)        = NoDoc
867 oneLiner (TextBeside s sl p) = textBeside_ s sl (oneLiner p)
868 oneLiner (Nest k p)          = nest_ k (oneLiner p)
869 oneLiner (p `Union` _)       = oneLiner p
870 oneLiner _                   = panic "oneLiner: Unhandled case"
871 \end{code}
872
873
874
875 %*********************************************************
876 %*                                                       *
877 \subsection{Displaying the best layout}
878 %*                                                       *
879 %*********************************************************
880
881
882 \begin{code}
883 {-
884 renderStyle Style{mode, lineLength, ribbonsPerLine} doc
885   = fullRender mode lineLength ribbonsPerLine doc ""
886 -}
887
888 render doc       = showDocWith PageMode doc
889
890 showDoc :: Doc -> String -> String
891 showDoc doc rest = showDocWithAppend PageMode doc rest
892
893 showDocWithAppend :: Mode -> Doc -> String -> String
894 showDocWithAppend mode doc rest = fullRender mode 100 1.5 string_txt rest doc
895
896 showDocWith :: Mode -> Doc -> String
897 showDocWith mode doc = showDocWithAppend mode doc ""
898
899 string_txt :: TextDetails -> String -> String
900 string_txt (Chr c)   s  = c:s
901 string_txt (Str s1)  s2 = s1 ++ s2
902 string_txt (PStr s1) s2 = unpackFS s1 ++ s2
903 string_txt (LStr s1 _) s2 = unpackLitString s1 ++ s2
904 \end{code}
905
906 \begin{code}
907
908 fullRender OneLineMode _ _ txt end doc
909   = lay (reduceDoc doc)
910   where
911     lay NoDoc              = cant_fail
912     lay (Union _ q)        = lay q -- Second arg can't be NoDoc
913     lay (Nest _ p)         = lay p
914     lay Empty              = end
915     lay (NilAbove p)       = space_text `txt` lay p -- NoDoc always on
916                                                     -- first line
917     lay (TextBeside s _ p) = s `txt` lay p
918     lay _                  = panic "fullRender/OneLineMode/lay: Unhandled case"
919
920 fullRender LeftMode    _ _ txt end doc
921   = lay (reduceDoc doc)
922   where
923     lay NoDoc              = cant_fail
924     lay (Union p q)        = lay (first p q)
925     lay (Nest _ p)         = lay p
926     lay Empty              = end
927     lay (NilAbove p)       = nl_text `txt` lay p -- NoDoc always on first line
928     lay (TextBeside s _ p) = s `txt` lay p
929     lay _                  = panic "fullRender/LeftMode/lay: Unhandled case"
930
931 fullRender mode line_length ribbons_per_line txt end doc
932   = display mode line_length ribbon_length txt end best_doc
933   where
934     best_doc = best hacked_line_length ribbon_length (reduceDoc doc)
935
936     hacked_line_length, ribbon_length :: Int
937     ribbon_length = round (fromIntegral line_length / ribbons_per_line)
938     hacked_line_length = case mode of
939                          ZigZagMode -> maxBound
940                          _ -> line_length
941
942 display :: Mode -> Int -> Int -> (TextDetails -> t -> t) -> t -> Doc -> t
943 display mode page_width ribbon_width txt end doc
944   = case (iUnbox page_width) -# (iUnbox ribbon_width) of { gap_width ->
945     case gap_width `quotFastInt` _ILIT(2) of { shift ->
946     let
947         lay k (Nest k1 p)  = lay (k +# k1) p
948         lay _ Empty        = end
949
950         lay k (NilAbove p) = nl_text `txt` lay k p
951
952         lay k (TextBeside s sl p)
953             = case mode of
954                     ZigZagMode |  k >=# gap_width
955                                -> nl_text `txt` (
956                                   Str (multi_ch shift '/') `txt` (
957                                   nl_text `txt` (
958                                   lay1 (k -# shift) s sl p)))
959
960                                |  k <# _ILIT(0)
961                                -> nl_text `txt` (
962                                   Str (multi_ch shift '\\') `txt` (
963                                   nl_text `txt` (
964                                   lay1 (k +# shift) s sl p )))
965
966                     _ -> lay1 k s sl p
967         lay _ _            = panic "display/lay: Unhandled case"
968
969         lay1 k s sl p = indent k (s `txt` lay2 (k +# sl) p)
970
971         lay2 k (NilAbove p)        = nl_text `txt` lay k p
972         lay2 k (TextBeside s sl p) = s `txt` (lay2 (k +# sl) p)
973         lay2 k (Nest _ p)          = lay2 k p
974         lay2 _ Empty               = end
975         lay2 _ _                   = panic "display/lay2: Unhandled case"
976
977         -- optimise long indentations using LitString chunks of 8 spaces
978         indent n r | n >=# _ILIT(8) = LStr (sLit "        ") (_ILIT(8)) `txt`
979                                       indent (n -# _ILIT(8)) r
980                    | otherwise      = Str (spaces n) `txt` r
981     in
982     lay (_ILIT(0)) doc
983     }}
984
985 cant_fail :: a
986 cant_fail = error "easy_display: NoDoc"
987
988 multi_ch :: Int# -> Char -> String
989 multi_ch n ch | n <=# _ILIT(0) = ""
990               | otherwise      = ch : multi_ch (n -# _ILIT(1)) ch
991
992 spaces :: Int# -> String
993 spaces n | n <=# _ILIT(0) = ""
994          | otherwise      = ' ' : spaces (n -# _ILIT(1))
995
996 \end{code}
997
998 \begin{code}
999 pprCols :: Int
1000 pprCols = 100 -- could make configurable
1001
1002 -- NB. printDoc prints FastStrings in UTF-8: hPutFS below does no decoding.
1003 -- This is what we usually want, because the IO library has no encoding
1004 -- functionality, and we're assuming UTF-8 source code so we might as well
1005 -- assume UTF-8 output too.
1006 printDoc :: Mode -> Handle -> Doc -> IO ()
1007 printDoc LeftMode hdl doc
1008   = do { printLeftRender hdl doc; hFlush hdl }
1009 printDoc mode hdl doc
1010   = do { fullRender mode pprCols 1.5 put done doc ;
1011          hFlush hdl }
1012   where
1013     put (Chr c)  next = hPutChar hdl c >> next
1014     put (Str s)  next = hPutStr  hdl s >> next
1015     put (PStr s) next = hPutFS   hdl s >> next
1016     put (LStr s l) next = hPutLitString hdl s l >> next
1017
1018     done = hPutChar hdl '\n'
1019
1020   -- some versions of hPutBuf will barf if the length is zero
1021 hPutLitString :: Handle -> Ptr a -> Int# -> IO ()
1022 hPutLitString handle a l = if l ==# _ILIT(0)
1023                             then return ()
1024                             else hPutBuf handle a (iBox l)
1025
1026 -- Printing output in LeftMode is performance critical: it's used when
1027 -- dumping C and assembly output, so we allow ourselves a few dirty
1028 -- hacks:
1029 --
1030 -- (1) we specialise fullRender for LeftMode with IO output.
1031 --
1032 -- (2) we add a layer of buffering on top of Handles.  Handles
1033 --     don't perform well with lots of hPutChars, which is mostly
1034 --     what we're doing here, because Handles have to be thread-safe
1035 --     and async exception-safe.  We only have a single thread and don't
1036 --     care about exceptions, so we add a layer of fast buffering
1037 --     over the Handle interface.
1038 --
1039 -- (3) a few hacks in layLeft below to convince GHC to generate the right
1040 --     code.
1041
1042 printLeftRender :: Handle -> Doc -> IO ()
1043 printLeftRender hdl doc = do
1044   b <- newBufHandle hdl
1045   layLeft b (reduceDoc doc)
1046   bFlush b
1047
1048 -- HACK ALERT!  the "return () >>" below convinces GHC to eta-expand
1049 -- this function with the IO state lambda.  Otherwise we end up with
1050 -- closures in all the case branches.
1051 layLeft :: BufHandle -> Doc -> IO ()
1052 layLeft b _ | b `seq` False  = undefined -- make it strict in b
1053 layLeft _ NoDoc              = cant_fail
1054 layLeft b (Union p q)        = return () >> layLeft b (first p q)
1055 layLeft b (Nest _ p)         = return () >> layLeft b p
1056 layLeft b Empty              = bPutChar b '\n'
1057 layLeft b (NilAbove p)       = bPutChar b '\n' >> layLeft b p
1058 layLeft b (TextBeside s _ p) = put b s >> layLeft b p
1059  where
1060     put b _ | b `seq` False = undefined
1061     put b (Chr c)    = bPutChar b c
1062     put b (Str s)    = bPutStr  b s
1063     put b (PStr s)   = bPutFS   b s
1064     put b (LStr s l) = bPutLitString b s l
1065 layLeft _ _                  = panic "layLeft: Unhandled case"
1066 \end{code}