X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2Futils%2FPretty.lhs;h=f0ca69cbb9eae6a0216c48ad1a10e36ddf28ef66;hp=7aec715d7a2ba3276d0d4263e5331492ee4d26e4;hb=e2e0785eb7f4efd9f7791d913cdfdfd03148cd86;hpb=66b17554b1415df8e505793802ccd14dee66d6db diff --git a/compiler/utils/Pretty.lhs b/compiler/utils/Pretty.lhs index 7aec715..f0ca69c 100644 --- a/compiler/utils/Pretty.lhs +++ b/compiler/utils/Pretty.lhs @@ -152,6 +152,7 @@ Relative to John's original paper, there are the following new features: \begin{code} +{-# LANGUAGE BangPatterns #-} {-# OPTIONS -fno-warn-unused-imports #-} -- XXX GHC 6.9 seems to be confused by unpackCString# being used only in -- a RULE @@ -162,7 +163,7 @@ module Pretty ( empty, isEmpty, nest, - char, text, ftext, ptext, + char, text, ftext, ptext, zeroWidthText, int, integer, float, double, rational, parens, brackets, braces, quotes, doubleQuotes, semi, comma, colon, space, equals, @@ -176,14 +177,15 @@ module Pretty ( hang, punctuate, -- renderStyle, -- Haskell 1.3 only - render, fullRender, printDoc, showDocWith + render, fullRender, printDoc, showDocWith, + bufLeftRender -- performance hack ) where import BufWrite import FastString import FastTypes import Panic - +import StaticFlags import Numeric (fromRat) import System.IO --import Foreign.Ptr (castPtr) @@ -222,6 +224,10 @@ The primitive @Doc@ values \begin{code} empty :: Doc isEmpty :: Doc -> Bool +-- | Some text, but without any width. Use for non-printing text +-- such as a HTML or Latex tags +zeroWidthText :: String -> Doc + text :: String -> Doc char :: Char -> Doc @@ -558,6 +564,7 @@ ftext s = case iUnbox (lengthFS s) of {sl -> textBeside_ (PStr s) sl Empty} ptext :: LitString -> Doc ptext s_= case iUnbox (lengthLS s) of {sl -> textBeside_ (LStr s sl) sl Empty} where s = {-castPtr-} s_ +zeroWidthText s = textBeside_ (Str s) (_ILIT(0)) Empty #if defined(__GLASGOW_HASKELL__) -- RULE that turns (text "abc") into (ptext (A# "abc"#)) to avoid the @@ -614,7 +621,7 @@ aboveNest (Nest k1 p) g k q = nest_ k1 (aboveNest p g (k -# k1) q) aboveNest (NilAbove p) g k q = nilAbove_ (aboveNest p g k q) aboveNest (TextBeside s sl p) g k q = textBeside_ s sl rest where - k1 = k -# sl + !k1 = k -# sl rest = case p of Empty -> nilAboveNest g k1 q _ -> aboveNest p g k1 q @@ -774,8 +781,8 @@ fillNB g Empty k (y:ys) = nilBeside g (fill1 g (oneLiner (reduceDoc y)) k1 ys `mkUnion` nilAboveNest False k (fill g (y:ys)) where - k1 | g = k -# _ILIT(1) - | otherwise = k + !k1 | g = k -# _ILIT(1) + | otherwise = k fillNB g p k ys = fill1 g p k ys \end{code} @@ -796,7 +803,7 @@ best :: Int -- Line length best w_ r_ p = get (iUnbox w_) p where - r = iUnbox r_ + !r = iUnbox r_ get :: FastInt -- (Remaining) width of line -> Doc -> Doc get _ Empty = Empty @@ -997,12 +1004,8 @@ spaces n | n <=# _ILIT(0) = "" \begin{code} pprCols :: Int -pprCols = 100 -- could make configurable +pprCols = opt_PprCols --- NB. printDoc prints FastStrings in UTF-8: hPutFS below does no decoding. --- This is what we usually want, because the IO library has no encoding --- functionality, and we're assuming UTF-8 source code so we might as well --- assume UTF-8 output too. printDoc :: Mode -> Handle -> Doc -> IO () printDoc LeftMode hdl doc = do { printLeftRender hdl doc; hFlush hdl } @@ -1012,7 +1015,9 @@ printDoc mode hdl doc where put (Chr c) next = hPutChar hdl c >> next put (Str s) next = hPutStr hdl s >> next - put (PStr s) next = hPutFS hdl s >> next + put (PStr s) next = hPutStr hdl (unpackFS s) >> next + -- NB. not hPutFS, we want this to go through + -- the I/O library's encoding layer. (#3398) put (LStr s l) next = hPutLitString hdl s l >> next done = hPutChar hdl '\n' @@ -1042,9 +1047,12 @@ hPutLitString handle a l = if l ==# _ILIT(0) printLeftRender :: Handle -> Doc -> IO () printLeftRender hdl doc = do b <- newBufHandle hdl - layLeft b (reduceDoc doc) + bufLeftRender b doc bFlush b +bufLeftRender :: BufHandle -> Doc -> IO () +bufLeftRender b doc = layLeft b (reduceDoc doc) + -- HACK ALERT! the "return () >>" below convinces GHC to eta-expand -- this function with the IO state lambda. Otherwise we end up with -- closures in all the case branches.