X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2Futils%2FOutputable.lhs;h=c8e454da900b0042d4b8df209e2d53e09f26aa65;hb=d923f167d8a1120c0e918330b44740f8f12b7f45;hp=c34404b2f8e9970426cf029af65b5d8d9b352872;hpb=dc52a1d0432805cdc0236f804953c7d948fd5db0;p=ghc-hetmet.git diff --git a/ghc/compiler/utils/Outputable.lhs b/ghc/compiler/utils/Outputable.lhs index c34404b..c8e454d 100644 --- a/ghc/compiler/utils/Outputable.lhs +++ b/ghc/compiler/utils/Outputable.lhs @@ -1,5 +1,5 @@ % -% (c) The GRASP Project, Glasgow University, 1992-1996 +% (c) The GRASP Project, Glasgow University, 1992-1998 % \section[Outputable]{Classes for pretty-printing} @@ -7,22 +7,23 @@ Defines classes for pretty-printing and forcing, both forms of ``output.'' \begin{code} + module Outputable ( Outputable(..), -- Class - PprStyle, + PprStyle, CodeStyle(..), PrintUnqualified, alwaysQualify, getPprStyle, withPprStyle, pprDeeper, codeStyle, ifaceStyle, userStyle, debugStyle, asmStyle, - ifPprDebug, ifNotPprForUser, + ifPprDebug, unqualStyle, SDoc, -- Abstract - interppSP, interpp'SP, pprQuotedList, + interppSP, interpp'SP, pprQuotedList, pprWithCommas, empty, nest, text, char, ptext, int, integer, float, double, rational, - parens, brackets, braces, quotes, doubleQuotes, - semi, comma, colon, space, equals, - lparen, rparen, lbrack, rbrack, lbrace, rbrace, + parens, brackets, braces, quotes, doubleQuotes, angleBrackets, + semi, comma, colon, dcolon, space, equals, dot, + lparen, rparen, lbrack, rbrack, lbrace, rbrace, underscore, (<>), (<+>), hcat, hsep, ($$), ($+$), vcat, sep, cat, @@ -30,24 +31,31 @@ module Outputable ( hang, punctuate, speakNth, speakNTimes, - showSDoc, printSDoc, printErrs, printDump, - printForC, printForAsm, printForIface, - pprCols, + printSDoc, printErrs, printDump, + printForC, printForAsm, printForIface, printForUser, + pprCode, pprCols, + showSDoc, showSDocForUser, showSDocDebug, showSDocIface, + showSDocUnqual, showsPrecSDoc, + pprHsChar, pprHsString, + -- error handling - pprPanic, pprPanic#, pprError, pprTrace, assertPprPanic, - panic, panic#, assertPanic + pprPanic, pprPanic#, pprError, pprTrace, assertPprPanic, warnPprTrace, + trace, panic, panic#, assertPanic ) where #include "HsVersions.h" + +import {-# SOURCE #-} Name( Name ) + import IO ( Handle, hPutChar, hPutStr, stderr, stdout ) -import CmdLineOpts ( opt_PprStyle_All, opt_PprStyle_Debug, opt_PprUserLength ) +import CmdLineOpts ( opt_PprStyle_Debug, opt_PprUserLength ) import FastString import qualified Pretty import Pretty ( Doc, Mode(..), TextDetails(..), fullRender ) -import Util ( panic, assertPanic, panic# ) -import GlaExts ( trace ) +import Panic +import Char ( chr, ord, isDigit ) \end{code} @@ -59,23 +67,36 @@ import GlaExts ( trace ) \begin{code} data PprStyle - = PprUser Depth -- Pretty-print in a way that will - -- make sense to the ordinary user; - -- must be very close to Haskell - -- syntax, etc. - - | PprDebug -- Standard debugging output + = PprUser PrintUnqualified Depth -- Pretty-print in a way that will + -- make sense to the ordinary user; + -- must be very close to Haskell + -- syntax, etc. - | PprInterface -- Interface generation + | PprInterface PrintUnqualified -- Interface generation | PprCode CodeStyle -- Print code; either C or assembler + | PprDebug -- Standard debugging output data CodeStyle = CStyle -- The format of labels differs for C and assembler | AsmStyle data Depth = AllTheWay | PartWay Int -- 0 => stop + + +type PrintUnqualified = Name -> Bool + -- This function tells when it's ok to print + -- a (Global) name unqualified + +alwaysQualify,neverQualify :: PrintUnqualified +alwaysQualify n = False +neverQualify n = True + +defaultUserStyle = mkUserStyle alwaysQualify AllTheWay + +mkUserStyle unqual depth | opt_PprStyle_Debug = PprDebug + | otherwise = PprUser unqual depth \end{code} Orthogonal to the above printing styles are (possibly) some @@ -99,15 +120,20 @@ withPprStyle :: PprStyle -> SDoc -> SDoc withPprStyle sty d sty' = d sty pprDeeper :: SDoc -> SDoc -pprDeeper d (PprUser (PartWay 0)) = Pretty.text "..." -pprDeeper d (PprUser (PartWay n)) = d (PprUser (PartWay (n-1))) -pprDeeper d other_sty = d other_sty +pprDeeper d (PprUser unqual (PartWay 0)) = Pretty.text "..." +pprDeeper d (PprUser unqual (PartWay n)) = d (PprUser unqual (PartWay (n-1))) +pprDeeper d other_sty = d other_sty getPprStyle :: (PprStyle -> SDoc) -> SDoc getPprStyle df sty = df sty sty \end{code} \begin{code} +unqualStyle :: PprStyle -> Name -> Bool +unqualStyle (PprUser unqual _) n = unqual n +unqualStyle (PprInterface unqual) n = unqual n +unqualStyle other n = False + codeStyle :: PprStyle -> Bool codeStyle (PprCode _) = True codeStyle _ = False @@ -117,22 +143,16 @@ asmStyle (PprCode AsmStyle) = True asmStyle other = False ifaceStyle :: PprStyle -> Bool -ifaceStyle PprInterface = True -ifaceStyle other = False +ifaceStyle (PprInterface _) = True +ifaceStyle other = False debugStyle :: PprStyle -> Bool debugStyle PprDebug = True debugStyle other = False userStyle :: PprStyle -> Bool -userStyle (PprUser _) = True -userStyle other = False -\end{code} - -\begin{code} -ifNotPprForUser :: SDoc -> SDoc -- Returns empty document for User style -ifNotPprForUser d sty@(PprUser _) = Pretty.empty -ifNotPprForUser d sty = d sty +userStyle (PprUser _ _) = True +userStyle other = False ifPprDebug :: SDoc -> SDoc -- Empty for non-debug style ifPprDebug d sty@PprDebug = d sty @@ -145,38 +165,60 @@ printSDoc d sty = printDoc PageMode stdout (d sty) -- I'm not sure whether the direct-IO approach of printDoc -- above is better or worse than the put-big-string approach here -printErrs :: SDoc -> IO () -printErrs doc = printDoc PageMode stderr (final_doc user_style) - where - final_doc = doc $$ text "" - user_style = mkUserStyle (PartWay opt_PprUserLength) +printErrs :: PrintUnqualified -> SDoc -> IO () +printErrs unqual doc = printDoc PageMode stderr (doc style) + where + style = mkUserStyle unqual (PartWay opt_PprUserLength) printDump :: SDoc -> IO () -printDump doc = printDoc PageMode stderr (final_doc PprDebug) - where - final_doc = doc $$ text "" +printDump doc = printDoc PageMode stdout (better_doc defaultUserStyle) + where + better_doc = doc $$ text "" + -- We used to always print in debug style, but I want + -- to try the effect of a more user-ish style (unless you + -- say -dppr-debug +printForUser :: Handle -> PrintUnqualified -> SDoc -> IO () +printForUser handle unqual doc + = printDoc PageMode handle (doc (mkUserStyle unqual AllTheWay)) --- printForC, printForAsm doe what they sound like +-- printForIface prints all on one line for interface files. +-- It's called repeatedly for successive lines +printForIface :: Handle -> PrintUnqualified -> SDoc -> IO () +printForIface handle unqual doc + = printDoc LeftMode handle (doc (PprInterface unqual)) + +-- printForC, printForAsm do what they sound like printForC :: Handle -> SDoc -> IO () printForC handle doc = printDoc LeftMode handle (doc (PprCode CStyle)) printForAsm :: Handle -> SDoc -> IO () printForAsm handle doc = printDoc LeftMode handle (doc (PprCode AsmStyle)) --- printForIface prints all on one line for interface files. --- It's called repeatedly for successive lines -printForIface :: Handle -> SDoc -> IO () -printForIface handle doc = printDoc OneLineMode handle (doc PprInterface) - +pprCode :: CodeStyle -> SDoc -> SDoc +pprCode cs d = withPprStyle (PprCode cs) d +-- Can't make SDoc an instance of Show because SDoc is just a function type +-- However, Doc *is* an instance of Show -- showSDoc just blasts it out as a string showSDoc :: SDoc -> String -showSDoc d = show (d (mkUserStyle AllTheWay)) +showSDoc d = show (d defaultUserStyle) + +showSDocForUser :: PrintUnqualified -> SDoc -> String +showSDocForUser unqual doc = show (doc (mkUserStyle unqual AllTheWay)) + +showSDocUnqual :: SDoc -> String +-- Only used in the gruesome HsExpr.isOperator +showSDocUnqual d = show (d (mkUserStyle neverQualify AllTheWay)) + +showsPrecSDoc :: Int -> SDoc -> ShowS +showsPrecSDoc p d = showsPrec p (d defaultUserStyle) -mkUserStyle depth | opt_PprStyle_Debug - || opt_PprStyle_All = PprDebug - | otherwise = PprUser depth +showSDocIface :: SDoc -> String +showSDocIface doc = showDocWith OneLineMode (doc (PprInterface alwaysQualify)) + +showSDocDebug :: SDoc -> String +showSDocDebug d = show (d PprDebug) \end{code} \begin{code} @@ -193,8 +235,17 @@ rational n sty = Pretty.rational n parens d sty = Pretty.parens (d sty) braces d sty = Pretty.braces (d sty) brackets d sty = Pretty.brackets (d sty) -quotes d sty = Pretty.quotes (d sty) doubleQuotes d sty = Pretty.doubleQuotes (d sty) +angleBrackets d = char '<' <> d <> char '>' + +-- quotes encloses something in single quotes... +-- but it omits them if the thing ends in a single quote +-- so that we don't get `foo''. Instead we just have foo'. +quotes d sty = case show pp_d of + ('\'' : _) -> pp_d + other -> Pretty.quotes pp_d + where + pp_d = d sty semi sty = Pretty.semi comma sty = Pretty.comma @@ -207,6 +258,9 @@ lbrack sty = Pretty.lbrack rbrack sty = Pretty.rbrack lbrace sty = Pretty.lbrace rbrace sty = Pretty.rbrace +dcolon sty = Pretty.ptext SLIT("::") +underscore = char '_' +dot = char '.' nest n d sty = Pretty.nest n (d sty) (<>) d1 d2 sty = (Pretty.<>) (d1 sty) (d2 sty) @@ -252,19 +306,78 @@ instance Outputable Bool where instance Outputable Int where ppr n = int n +instance Outputable () where + ppr _ = text "()" + instance (Outputable a) => Outputable [a] where ppr xs = brackets (fsep (punctuate comma (map ppr xs))) instance (Outputable a, Outputable b) => Outputable (a, b) where - ppr (x,y) = - hang (hcat [lparen, ppr x, comma]) 4 ((<>) (ppr y) rparen) + ppr (x,y) = parens (sep [ppr x <> comma, ppr y]) + +instance Outputable a => Outputable (Maybe a) where + ppr Nothing = ptext SLIT("Nothing") + ppr (Just x) = ptext SLIT("Just") <+> ppr x -- ToDo: may not be used instance (Outputable a, Outputable b, Outputable c) => Outputable (a, b, c) where ppr (x,y,z) = - parens (sep [ (<>) (ppr x) comma, - (<>) (ppr y) comma, - ppr z ]) + parens (sep [ppr x <> comma, + ppr y <> comma, + ppr z ]) + +instance (Outputable a, Outputable b, Outputable c, Outputable d) => + Outputable (a, b, c, d) where + ppr (x,y,z,w) = + parens (sep [ppr x <> comma, + ppr y <> comma, + ppr z <> comma, + ppr w]) + +instance Outputable FastString where + ppr fs = text (unpackFS fs) -- Prints an unadorned string, + -- no double quotes or anything + +#if __GLASGOW_HASKELL__ < 410 +-- Assume we have only 8-bit Chars. + +pprHsChar :: Int -> SDoc +pprHsChar c = char '\'' <> text (showCharLit c "") <> char '\'' + +pprHsString :: FAST_STRING -> SDoc +pprHsString fs = doubleQuotes (text (foldr showCharLit "" (_UNPK_INT_ fs))) + +showCharLit :: Int -> String -> String +showCharLit c rest + | c == ord '\"' = "\\\"" ++ rest + | c == ord '\'' = "\\\'" ++ rest + | c == ord '\\' = "\\\\" ++ rest + | c >= 0x20 && c <= 0x7E = chr c : rest + | c == ord '\a' = "\\a" ++ rest + | c == ord '\b' = "\\b" ++ rest + | c == ord '\f' = "\\f" ++ rest + | c == ord '\n' = "\\n" ++ rest + | c == ord '\r' = "\\r" ++ rest + | c == ord '\t' = "\\t" ++ rest + | c == ord '\v' = "\\v" ++ rest + | otherwise = ('\\':) $ shows c $ case rest of + d:_ | isDigit d -> "\\&" ++ rest + _ -> rest + +#else +-- We have 31-bit Chars and will simply use Show instances +-- of Char and String. + +pprHsChar :: Int -> SDoc +pprHsChar c = text (show (chr c)) + +pprHsString :: FastString -> SDoc +pprHsString fs = text (show (unpackFS fs)) + +#endif + +instance Show FastString where + showsPrec p fs = showsPrecSDoc p (ppr fs) \end{code} @@ -286,10 +399,21 @@ printDoc mode hdl doc put (PStr s) next = hPutFS hdl s >> next done = hPutChar hdl '\n' + +showDocWith :: Mode -> Doc -> String +showDocWith mode doc + = fullRender mode 100 1.5 put "" doc + where + put (Chr c) s = c:s + put (Str s1) s2 = s1 ++ s2 + put (PStr s1) s2 = _UNPK_ s1 ++ s2 \end{code} \begin{code} +pprWithCommas :: (a -> SDoc) -> [a] -> SDoc +pprWithCommas pp xs = hsep (punctuate comma (map pp xs)) + interppSP :: Outputable a => [a] -> SDoc interppSP xs = hsep (map ppr xs) @@ -302,8 +426,6 @@ pprQuotedList xs = hsep (punctuate comma (map (quotes . ppr) xs)) \end{code} - - %************************************************************************ %* * \subsection{Printing numbers verbally} @@ -339,27 +461,30 @@ speakNTimes t | t == 1 = ptext SLIT("once") | otherwise = int t <+> ptext SLIT("times") \end{code} + %************************************************************************ %* * -\subsection[Utils-errors]{Error handling} +\subsection{Error handling} %* * %************************************************************************ \begin{code} -pprPanic heading pretty_msg = panic (show (doc PprDebug)) - where - doc = text heading <+> pretty_msg - -pprError heading pretty_msg = error (heading++ " " ++ (show pretty_msg)) - -pprTrace heading pretty_msg = trace (show (doc PprDebug)) - where - doc = text heading <+> pretty_msg +pprPanic :: String -> SDoc -> a +pprError :: String -> SDoc -> a +pprTrace :: String -> SDoc -> a -> a +pprPanic = pprAndThen panic +pprError = pprAndThen error +pprTrace = pprAndThen trace pprPanic# heading pretty_msg = panic# (show (doc PprDebug)) where doc = text heading <+> pretty_msg +pprAndThen :: (String -> a) -> String -> SDoc -> a +pprAndThen cont heading pretty_msg = cont (show (doc PprDebug)) + where + doc = sep [text heading, nest 4 pretty_msg] + assertPprPanic :: String -> Int -> SDoc -> a assertPprPanic file line msg = panic (show (doc PprDebug)) @@ -368,4 +493,12 @@ assertPprPanic file line msg text file, text "line", int line], msg] + +warnPprTrace :: Bool -> String -> Int -> SDoc -> a -> a +warnPprTrace False file line msg x = x +warnPprTrace True file line msg x + = trace (show (doc PprDebug)) x + where + doc = sep [hsep [text "WARNING: file", text file, text "line", int line], + msg] \end{code}