[project @ 2001-04-27 08:31:54 by simonmar]
[ghc-hetmet.git] / ghc / compiler / utils / Outputable.lhs
index 586f44e..2dd48ce 100644 (file)
@@ -7,17 +7,14 @@ Defines classes for pretty-printing and forcing, both forms of
 ``output.''
 
 \begin{code}
-{-# OPTIONS -fno-prune-tydecls #-}
--- Hopefully temporary; 3.02 complained about not being able
--- to see the consructors for ForeignObj
 
 module Outputable (
        Outputable(..),                 -- Class
 
-       PprStyle, CodeStyle(..), 
+       PprStyle, CodeStyle(..), PrintUnqualified, alwaysQualify,
        getPprStyle, withPprStyle, pprDeeper,
        codeStyle, ifaceStyle, userStyle, debugStyle, asmStyle,
-       ifPprDebug, ifNotPprForUser,
+       ifPprDebug, unqualStyle,
 
        SDoc,           -- Abstract
        interppSP, interpp'SP, pprQuotedList, pprWithCommas,
@@ -34,11 +31,12 @@ module Outputable (
        hang, punctuate,
        speakNth, speakNTimes,
 
-       printSDoc, printErrs, printDump, 
+       printSDoc, printErrs, printDump,
        printForC, printForAsm, printForIface, printForUser,
        pprCode, pprCols,
-       showSDoc, showSDocDebug, showSDocIface, showsPrecSDoc, 
-       pprFSAsString,
+       showSDoc, showSDocForUser, showSDocDebug, showSDocIface, 
+       showSDocUnqual, showsPrecSDoc,
+       pprHsChar, pprHsString,
 
 
        -- error handling
@@ -49,14 +47,17 @@ module Outputable (
 #include "HsVersions.h"
 
 
-import IO              ( Handle, hPutChar, hPutStr, stderr, stdout )
+import {-# SOURCE #-}  Name( Name )
+
 import CmdLineOpts     ( opt_PprStyle_Debug, opt_PprUserLength )
 import FastString
 import qualified Pretty
 import Pretty          ( Doc, Mode(..), TextDetails(..), fullRender )
 import Panic
-import ST              ( runST )
-import Foreign
+
+import Word            ( Word32 )
+import IO              ( Handle, hPutChar, hPutStr, stderr, stdout )
+import Char             ( chr, ord, isDigit )
 \end{code}
 
 
@@ -68,23 +69,36 @@ import Foreign
 
 \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.
+  = PprUser PrintUnqualified 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
-
-  | 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
@@ -108,15 +122,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
@@ -126,22 +145,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
@@ -154,20 +167,28 @@ 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 stdout (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 = printForUser stdout (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
+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))
 
-printForUser :: Handle -> SDoc -> IO ()
-printForUser handle doc = printDoc PageMode handle (doc (mkUserStyle AllTheWay))
+-- 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 ()
@@ -176,11 +197,6 @@ 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
 
@@ -188,19 +204,23 @@ pprCode cs d = withPprStyle (PprCode cs) d
 -- 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)
 
-showSDocIface :: SDoc -> String
-showSDocIface doc = showDocWith OneLineMode (doc PprInterface)
+showSDocForUser :: PrintUnqualified -> SDoc -> String
+showSDocForUser unqual doc = show (doc (mkUserStyle unqual AllTheWay))
 
-showSDocDebug :: SDoc -> String
-showSDocDebug d = show (d PprDebug)
+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 (mkUserStyle AllTheWay))
+showsPrecSDoc p d = showsPrec p (d defaultUserStyle)
+
+showSDocIface :: SDoc -> String
+showSDocIface doc = showDocWith OneLineMode (doc (PprInterface alwaysQualify))
 
-mkUserStyle depth |  opt_PprStyle_Debug = PprDebug
-                 |  otherwise          = PprUser depth
+showSDocDebug :: SDoc -> String
+showSDocDebug d = show (d PprDebug)
 \end{code}
 
 \begin{code}
@@ -288,6 +308,9 @@ 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)))
 
@@ -295,8 +318,8 @@ instance (Outputable a, Outputable b) => Outputable (a, b) where
     ppr (x,y) = parens (sep [ppr x <> comma, ppr y])
 
 instance Outputable a => Outputable (Maybe a) where
-  ppr Nothing = text "Nothing"
-  ppr (Just x) = text "Just" <+> ppr x
+  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
@@ -317,8 +340,44 @@ instance Outputable FastString where
     ppr fs = text (unpackFS fs)                -- Prints an unadorned string,
                                        -- no double quotes or anything
 
-pprFSAsString :: FastString -> SDoc                    -- The Char instance of Show prints
-pprFSAsString fs = text (showList (unpackFS fs) "")    -- strings with double quotes and escapes
+#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 (fromIntegral c :: Word32) $ 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 | c > 0x10ffff = char '\\' <> show (fromIntegral c :: Word32)
+            | otherwise    = 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)
@@ -346,7 +405,7 @@ printDoc mode hdl doc
 
 showDocWith :: Mode -> Doc -> String
 showDocWith mode doc
-  = fullRender PageMode 100 1.5 put "" doc
+  = fullRender mode 100 1.5 put "" doc
   where
     put (Chr c)   s  = c:s
     put (Str s1)  s2 = s1 ++ s2