Fix Trac #3012: allow more free-wheeling in standalone deriving
[ghc-hetmet.git] / compiler / utils / Outputable.lhs
1 %
2 % (c) The University of Glasgow 2006
3 % (c) The GRASP Project, Glasgow University, 1992-1998
4 %
5
6 \begin{code}
7 -- | This module defines classes and functions for pretty-printing. It also
8 -- exports a number of helpful debugging and other utilities such as 'trace' and 'panic'.
9 --
10 -- The interface to this module is very similar to the standard Hughes-PJ pretty printing
11 -- module, except that it exports a number of additional functions that are rarely used,
12 -- and works over the 'SDoc' type.
13 module Outputable (
14         -- * Type classes
15         Outputable(..), OutputableBndr(..),
16
17         -- * Pretty printing combinators
18         SDoc,
19         docToSDoc,
20         interppSP, interpp'SP, pprQuotedList, pprWithCommas,
21         empty, nest,
22         char,
23         text, ftext, ptext,
24         int, integer, float, double, rational,
25         parens, cparen, brackets, braces, quotes, doubleQuotes, angleBrackets,
26         semi, comma, colon, dcolon, space, equals, dot, arrow,
27         lparen, rparen, lbrack, rbrack, lbrace, rbrace, underscore,
28         (<>), (<+>), hcat, hsep, 
29         ($$), ($+$), vcat,
30         sep, cat, 
31         fsep, fcat, 
32         hang, punctuate,
33         speakNth, speakNTimes, speakN, speakNOf, plural,
34
35         -- * Converting 'SDoc' into strings and outputing it
36         printSDoc, printErrs, hPrintDump, printDump,
37         printForC, printForAsm, printForUser, printForUserPartWay,
38         pprCode, mkCodeStyle,
39         showSDoc, showSDocOneLine,
40         showSDocForUser, showSDocDebug, showSDocDump, showSDocDumpOneLine,
41         showPpr,
42         showSDocUnqual, showsPrecSDoc,
43
44         pprInfixVar, pprPrefixVar,
45         pprHsChar, pprHsString, pprHsInfix, pprHsVar,
46         pprFastFilePath,
47
48         -- * Controlling the style in which output is printed
49         BindingSite(..),
50
51         PprStyle, CodeStyle(..), PrintUnqualified, alwaysQualify, neverQualify,
52         QualifyName(..),
53         getPprStyle, withPprStyle, withPprStyleDoc, 
54         pprDeeper, pprDeeperList, pprSetDepth,
55         codeStyle, userStyle, debugStyle, dumpStyle, asmStyle,
56         ifPprDebug, qualName, qualModule,
57         mkErrStyle, defaultErrStyle, defaultDumpStyle, defaultUserStyle,
58         mkUserStyle, Depth(..),
59
60         -- * Error handling and debugging utilities
61         pprPanic, assertPprPanic, pprPanicFastInt, pprPgmError, 
62         pprTrace, warnPprTrace,
63         trace, pgmError, panic, panicFastInt, assertPanic
64     ) where
65
66 import {-# SOURCE #-}   Module( Module, ModuleName, moduleName )
67 import {-# SOURCE #-}   OccName( OccName )
68
69 import StaticFlags
70 import FastString 
71 import FastTypes
72 import qualified Pretty
73 import Pretty           ( Doc, Mode(..) )
74 import Char             ( isAlpha )
75 import Panic
76
77 import Data.Word        ( Word32 )
78 import System.IO        ( Handle, stderr, stdout, hFlush )
79 import Data.Char        ( ord )
80 import System.FilePath
81 \end{code}
82
83
84 %************************************************************************
85 %*                                                                      *
86 \subsection{The @PprStyle@ data type}
87 %*                                                                      *
88 %************************************************************************
89
90 \begin{code}
91
92 data PprStyle
93   = PprUser PrintUnqualified Depth
94                 -- Pretty-print in a way that will make sense to the
95                 -- ordinary user; must be very close to Haskell
96                 -- syntax, etc.
97                 -- Assumes printing tidied code: non-system names are
98                 -- printed without uniques.
99
100   | PprCode CodeStyle
101                 -- Print code; either C or assembler
102
103   | PprDump     -- For -ddump-foo; less verbose than PprDebug.
104                 -- Does not assume tidied code: non-external names
105                 -- are printed with uniques.
106
107   | PprDebug    -- Full debugging output
108
109 data CodeStyle = CStyle         -- The format of labels differs for C and assembler
110                | AsmStyle
111
112 data Depth = AllTheWay
113            | PartWay Int        -- 0 => stop
114
115
116 -- -----------------------------------------------------------------------------
117 -- Printing original names
118
119 -- When printing code that contains original names, we need to map the
120 -- original names back to something the user understands.  This is the
121 -- purpose of the pair of functions that gets passed around
122 -- when rendering 'SDoc'.
123
124 -- | given an /original/ name, this function tells you which module
125 -- name it should be qualified with when printing for the user, if
126 -- any.  For example, given @Control.Exception.catch@, which is in scope
127 -- as @Exception.catch@, this fuction will return @Just "Exception"@.
128 -- Note that the return value is a ModuleName, not a Module, because
129 -- in source code, names are qualified by ModuleNames.
130 type QueryQualifyName = Module -> OccName -> QualifyName
131
132 -- See Note [Printing original names] in HscTypes
133 data QualifyName                        -- given P:M.T
134         = NameUnqual                    -- refer to it as "T"
135         | NameQual ModuleName           -- refer to it as "X.T" for the supplied X
136         | NameNotInScope1               
137                 -- it is not in scope at all, but M.T is not bound in the current
138                 -- scope, so we can refer to it as "M.T"
139         | NameNotInScope2
140                 -- it is not in scope at all, and M.T is already bound in the
141                 -- current scope, so we must refer to it as "P:M.T"
142
143
144 -- | For a given module, we need to know whether to print it with
145 -- a package name to disambiguate it.
146 type QueryQualifyModule = Module -> Bool
147
148 type PrintUnqualified = (QueryQualifyName, QueryQualifyModule)
149
150 alwaysQualifyNames :: QueryQualifyName
151 alwaysQualifyNames m _ = NameQual (moduleName m)
152
153 neverQualifyNames :: QueryQualifyName
154 neverQualifyNames _ _ = NameUnqual
155
156 alwaysQualifyModules :: QueryQualifyModule
157 alwaysQualifyModules _ = True
158
159 neverQualifyModules :: QueryQualifyModule
160 neverQualifyModules _ = False
161
162 alwaysQualify, neverQualify :: PrintUnqualified
163 alwaysQualify = (alwaysQualifyNames, alwaysQualifyModules)
164 neverQualify  = (neverQualifyNames,  neverQualifyModules)
165
166 defaultUserStyle, defaultDumpStyle :: PprStyle
167
168 defaultUserStyle = mkUserStyle alwaysQualify AllTheWay
169
170 defaultDumpStyle |  opt_PprStyle_Debug = PprDebug
171                  |  otherwise          = PprDump
172
173 -- | Style for printing error messages
174 mkErrStyle :: PrintUnqualified -> PprStyle
175 mkErrStyle qual = mkUserStyle qual (PartWay opt_PprUserLength)
176
177 defaultErrStyle :: PprStyle
178 -- Default style for error messages
179 -- It's a bit of a hack because it doesn't take into account what's in scope
180 -- Only used for desugarer warnings, and typechecker errors in interface sigs
181 defaultErrStyle 
182   | opt_PprStyle_Debug   = mkUserStyle alwaysQualify AllTheWay
183   | otherwise            = mkUserStyle alwaysQualify (PartWay opt_PprUserLength)
184
185 mkUserStyle :: PrintUnqualified -> Depth -> PprStyle
186 mkUserStyle unqual depth
187    | opt_PprStyle_Debug = PprDebug
188    | otherwise          = PprUser unqual depth
189 \end{code}
190
191 Orthogonal to the above printing styles are (possibly) some
192 command-line flags that affect printing (often carried with the
193 style).  The most likely ones are variations on how much type info is
194 shown.
195
196 The following test decides whether or not we are actually generating
197 code (either C or assembly), or generating interface files.
198
199 %************************************************************************
200 %*                                                                      *
201 \subsection{The @SDoc@ data type}
202 %*                                                                      *
203 %************************************************************************
204
205 \begin{code}
206 type SDoc = PprStyle -> Doc
207
208 withPprStyle :: PprStyle -> SDoc -> SDoc
209 withPprStyle sty d _sty' = d sty
210
211 withPprStyleDoc :: PprStyle -> SDoc -> Doc
212 withPprStyleDoc sty d = d sty
213
214 pprDeeper :: SDoc -> SDoc
215 pprDeeper _ (PprUser _ (PartWay 0)) = Pretty.text "..."
216 pprDeeper d (PprUser q (PartWay n)) = d (PprUser q (PartWay (n-1)))
217 pprDeeper d other_sty               = d other_sty
218
219 pprDeeperList :: ([SDoc] -> SDoc) -> [SDoc] -> SDoc
220 -- Truncate a list that list that is longer than the current depth
221 pprDeeperList f ds (PprUser q (PartWay n))
222   | n==0      = Pretty.text "..."
223   | otherwise = f (go 0 ds) (PprUser q (PartWay (n-1)))
224   where
225     go _ [] = []
226     go i (d:ds) | i >= n    = [text "...."]
227                 | otherwise = d : go (i+1) ds
228
229 pprDeeperList f ds other_sty
230   = f ds other_sty
231
232 pprSetDepth :: Depth -> SDoc -> SDoc
233 pprSetDepth depth  doc (PprUser q _) = doc (PprUser q depth)
234 pprSetDepth _depth doc other_sty     = doc other_sty
235
236 getPprStyle :: (PprStyle -> SDoc) -> SDoc
237 getPprStyle df sty = df sty sty
238 \end{code}
239
240 \begin{code}
241 qualName :: PprStyle -> QueryQualifyName
242 qualName (PprUser (qual_name,_) _) m  n = qual_name m n
243 qualName _other                    m _n = NameQual (moduleName m)
244
245 qualModule :: PprStyle -> QueryQualifyModule
246 qualModule (PprUser (_,qual_mod) _)  m = qual_mod m
247 qualModule _other                   _m = True
248
249 codeStyle :: PprStyle -> Bool
250 codeStyle (PprCode _)     = True
251 codeStyle _               = False
252
253 asmStyle :: PprStyle -> Bool
254 asmStyle (PprCode AsmStyle)  = True
255 asmStyle _other              = False
256
257 dumpStyle :: PprStyle -> Bool
258 dumpStyle PprDump = True
259 dumpStyle _other  = False
260
261 debugStyle :: PprStyle -> Bool
262 debugStyle PprDebug       = True
263 debugStyle _other         = False
264
265 userStyle ::  PprStyle -> Bool
266 userStyle (PprUser _ _) = True
267 userStyle _other        = False
268
269 ifPprDebug :: SDoc -> SDoc        -- Empty for non-debug style
270 ifPprDebug d sty@PprDebug = d sty
271 ifPprDebug _ _            = Pretty.empty
272 \end{code}
273
274 \begin{code}
275 -- Unused [7/02 sof]
276 printSDoc :: SDoc -> PprStyle -> IO ()
277 printSDoc d sty = do
278   Pretty.printDoc PageMode stdout (d sty)
279   hFlush stdout
280
281 -- I'm not sure whether the direct-IO approach of Pretty.printDoc
282 -- above is better or worse than the put-big-string approach here
283 printErrs :: Doc -> IO ()
284 printErrs doc = do Pretty.printDoc PageMode stderr doc
285                    hFlush stderr
286
287 printDump :: SDoc -> IO ()
288 printDump doc = hPrintDump stdout doc
289
290 hPrintDump :: Handle -> SDoc -> IO ()
291 hPrintDump h doc = do
292    Pretty.printDoc PageMode h (better_doc defaultDumpStyle)
293    hFlush h
294  where
295    better_doc = doc $$ text ""
296
297 printForUser :: Handle -> PrintUnqualified -> SDoc -> IO ()
298 printForUser handle unqual doc 
299   = Pretty.printDoc PageMode handle (doc (mkUserStyle unqual AllTheWay))
300
301 printForUserPartWay :: Handle -> Int -> PrintUnqualified -> SDoc -> IO ()
302 printForUserPartWay handle d unqual doc
303   = Pretty.printDoc PageMode handle (doc (mkUserStyle unqual (PartWay d)))
304
305 -- printForC, printForAsm do what they sound like
306 printForC :: Handle -> SDoc -> IO ()
307 printForC handle doc = Pretty.printDoc LeftMode handle (doc (PprCode CStyle))
308
309 printForAsm :: Handle -> SDoc -> IO ()
310 printForAsm handle doc = Pretty.printDoc LeftMode handle (doc (PprCode AsmStyle))
311
312 pprCode :: CodeStyle -> SDoc -> SDoc
313 pprCode cs d = withPprStyle (PprCode cs) d
314
315 mkCodeStyle :: CodeStyle -> PprStyle
316 mkCodeStyle = PprCode
317
318 -- Can't make SDoc an instance of Show because SDoc is just a function type
319 -- However, Doc *is* an instance of Show
320 -- showSDoc just blasts it out as a string
321 showSDoc :: SDoc -> String
322 showSDoc d = Pretty.showDocWith PageMode (d defaultUserStyle)
323
324 -- This shows an SDoc, but on one line only. It's cheaper than a full
325 -- showSDoc, designed for when we're getting results like "Foo.bar"
326 -- and "foo{uniq strictness}" so we don't want fancy layout anyway.
327 showSDocOneLine :: SDoc -> String
328 showSDocOneLine d = Pretty.showDocWith PageMode (d defaultUserStyle)
329
330 showSDocForUser :: PrintUnqualified -> SDoc -> String
331 showSDocForUser unqual doc = show (doc (mkUserStyle unqual AllTheWay))
332
333 showSDocUnqual :: SDoc -> String
334 -- Only used in the gruesome isOperator
335 showSDocUnqual d = show (d (mkUserStyle neverQualify AllTheWay))
336
337 showsPrecSDoc :: Int -> SDoc -> ShowS
338 showsPrecSDoc p d = showsPrec p (d defaultUserStyle)
339
340 showSDocDump :: SDoc -> String
341 showSDocDump d = Pretty.showDocWith PageMode (d PprDump)
342
343 showSDocDumpOneLine :: SDoc -> String
344 showSDocDumpOneLine d = Pretty.showDocWith OneLineMode (d PprDump)
345
346 showSDocDebug :: SDoc -> String
347 showSDocDebug d = show (d PprDebug)
348
349 showPpr :: Outputable a => a -> String
350 showPpr = showSDoc . ppr
351 \end{code}
352
353 \begin{code}
354 docToSDoc :: Doc -> SDoc
355 docToSDoc d = \_ -> d
356
357 empty    :: SDoc
358 char     :: Char       -> SDoc
359 text     :: String     -> SDoc
360 ftext    :: FastString -> SDoc
361 ptext    :: LitString  -> SDoc
362 int      :: Int        -> SDoc
363 integer  :: Integer    -> SDoc
364 float    :: Float      -> SDoc
365 double   :: Double     -> SDoc
366 rational :: Rational   -> SDoc
367
368 empty _sty      = Pretty.empty
369 char c _sty     = Pretty.char c
370 text s _sty     = Pretty.text s
371 ftext s _sty    = Pretty.ftext s
372 ptext s _sty    = Pretty.ptext s
373 int n _sty      = Pretty.int n
374 integer n _sty  = Pretty.integer n
375 float n _sty    = Pretty.float n
376 double n _sty   = Pretty.double n
377 rational n _sty = Pretty.rational n
378
379 parens, braces, brackets, quotes, doubleQuotes, angleBrackets :: SDoc -> SDoc
380
381 parens d sty       = Pretty.parens (d sty)
382 braces d sty       = Pretty.braces (d sty)
383 brackets d sty     = Pretty.brackets (d sty)
384 doubleQuotes d sty = Pretty.doubleQuotes (d sty)
385 angleBrackets d    = char '<' <> d <> char '>'
386
387 cparen :: Bool -> SDoc -> SDoc
388
389 cparen b d sty       = Pretty.cparen b (d sty)
390
391 -- quotes encloses something in single quotes...
392 -- but it omits them if the thing ends in a single quote
393 -- so that we don't get `foo''.  Instead we just have foo'.
394 quotes d sty = case show pp_d of
395                  ('\'' : _) -> pp_d
396                  _other     -> Pretty.quotes pp_d
397              where
398                pp_d = d sty
399
400 semi, comma, colon, equals, space, dcolon, arrow, underscore, dot :: SDoc
401 lparen, rparen, lbrack, rbrack, lbrace, rbrace :: SDoc
402
403 semi _sty   = Pretty.semi
404 comma _sty  = Pretty.comma
405 colon _sty  = Pretty.colon
406 equals _sty = Pretty.equals
407 space _sty  = Pretty.space
408 dcolon _sty = Pretty.ptext (sLit "::")
409 arrow  _sty = Pretty.ptext (sLit "->")
410 underscore  = char '_'
411 dot         = char '.'
412 lparen _sty = Pretty.lparen
413 rparen _sty = Pretty.rparen
414 lbrack _sty = Pretty.lbrack
415 rbrack _sty = Pretty.rbrack
416 lbrace _sty = Pretty.lbrace
417 rbrace _sty = Pretty.rbrace
418
419 nest :: Int -> SDoc -> SDoc
420 -- ^ Indent 'SDoc' some specified amount
421 (<>) :: SDoc -> SDoc -> SDoc
422 -- ^ Join two 'SDoc' together horizontally without a gap
423 (<+>) :: SDoc -> SDoc -> SDoc
424 -- ^ Join two 'SDoc' together horizontally with a gap between them
425 ($$) :: SDoc -> SDoc -> SDoc
426 -- ^ Join two 'SDoc' together vertically; if there is 
427 -- no vertical overlap it "dovetails" the two onto one line
428 ($+$) :: SDoc -> SDoc -> SDoc
429 -- ^ Join two 'SDoc' together vertically
430
431 nest n d sty    = Pretty.nest n (d sty)
432 (<>) d1 d2 sty  = (Pretty.<>)  (d1 sty) (d2 sty)
433 (<+>) d1 d2 sty = (Pretty.<+>) (d1 sty) (d2 sty)
434 ($$) d1 d2 sty  = (Pretty.$$)  (d1 sty) (d2 sty)
435 ($+$) d1 d2 sty = (Pretty.$+$) (d1 sty) (d2 sty)
436
437 hcat :: [SDoc] -> SDoc
438 -- ^ Concatenate 'SDoc' horizontally
439 hsep :: [SDoc] -> SDoc
440 -- ^ Concatenate 'SDoc' horizontally with a space between each one
441 vcat :: [SDoc] -> SDoc
442 -- ^ Concatenate 'SDoc' vertically with dovetailing
443 sep :: [SDoc] -> SDoc
444 -- ^ Separate: is either like 'hsep' or like 'vcat', depending on what fits
445 cat :: [SDoc] -> SDoc
446 -- ^ Catenate: is either like 'hcat' or like 'vcat', depending on what fits
447 fsep :: [SDoc] -> SDoc
448 -- ^ A paragraph-fill combinator. It's much like sep, only it
449 -- keeps fitting things on one line until it can't fit any more.
450 fcat :: [SDoc] -> SDoc
451 -- ^ This behaves like 'fsep', but it uses '<>' for horizontal conposition rather than '<+>'
452
453
454 hcat ds sty = Pretty.hcat [d sty | d <- ds]
455 hsep ds sty = Pretty.hsep [d sty | d <- ds]
456 vcat ds sty = Pretty.vcat [d sty | d <- ds]
457 sep ds sty  = Pretty.sep  [d sty | d <- ds]
458 cat ds sty  = Pretty.cat  [d sty | d <- ds]
459 fsep ds sty = Pretty.fsep [d sty | d <- ds]
460 fcat ds sty = Pretty.fcat [d sty | d <- ds]
461
462 hang :: SDoc  -- ^ The header
463       -> Int  -- ^ Amount to indent the hung body
464       -> SDoc -- ^ The hung body, indented and placed below the header
465       -> SDoc
466 hang d1 n d2 sty   = Pretty.hang (d1 sty) n (d2 sty)
467
468 punctuate :: SDoc   -- ^ The punctuation
469           -> [SDoc] -- ^ The list that will have punctuation added between every adjacent pair of elements
470           -> [SDoc] -- ^ Punctuated list
471 punctuate _ []     = []
472 punctuate p (d:ds) = go d ds
473                    where
474                      go d [] = [d]
475                      go d (e:es) = (d <> p) : go e es
476 \end{code}
477
478
479 %************************************************************************
480 %*                                                                      *
481 \subsection[Outputable-class]{The @Outputable@ class}
482 %*                                                                      *
483 %************************************************************************
484
485 \begin{code}
486 -- | Class designating that some type has an 'SDoc' representation
487 class Outputable a where
488         ppr :: a -> SDoc
489 \end{code}
490
491 \begin{code}
492 instance Outputable Bool where
493     ppr True  = ptext (sLit "True")
494     ppr False = ptext (sLit "False")
495
496 instance Outputable Int where
497    ppr n = int n
498
499 instance Outputable Word32 where
500    ppr n = integer $ fromIntegral n
501
502 instance Outputable () where
503    ppr _ = text "()"
504
505 instance (Outputable a) => Outputable [a] where
506     ppr xs = brackets (fsep (punctuate comma (map ppr xs)))
507
508 instance (Outputable a, Outputable b) => Outputable (a, b) where
509     ppr (x,y) = parens (sep [ppr x <> comma, ppr y])
510
511 instance Outputable a => Outputable (Maybe a) where
512   ppr Nothing = ptext (sLit "Nothing")
513   ppr (Just x) = ptext (sLit "Just") <+> ppr x
514
515 instance (Outputable a, Outputable b) => Outputable (Either a b) where
516   ppr (Left x)  = ptext (sLit "Left")  <+> ppr x
517   ppr (Right y) = ptext (sLit "Right") <+> ppr y
518
519 -- ToDo: may not be used
520 instance (Outputable a, Outputable b, Outputable c) => Outputable (a, b, c) where
521     ppr (x,y,z) =
522       parens (sep [ppr x <> comma,
523                    ppr y <> comma,
524                    ppr z ])
525
526 instance (Outputable a, Outputable b, Outputable c, Outputable d) =>
527          Outputable (a, b, c, d) where
528     ppr (a,b,c,d) =
529       parens (sep [ppr a <> comma,
530                    ppr b <> comma,
531                    ppr c <> comma,
532                    ppr d])
533
534 instance (Outputable a, Outputable b, Outputable c, Outputable d, Outputable e) =>
535          Outputable (a, b, c, d, e) where
536     ppr (a,b,c,d,e) =
537       parens (sep [ppr a <> comma,
538                    ppr b <> comma,
539                    ppr c <> comma,
540                    ppr d <> comma,
541                    ppr e])
542
543 instance Outputable FastString where
544     ppr fs = ftext fs           -- Prints an unadorned string,
545                                 -- no double quotes or anything
546 \end{code}
547
548 %************************************************************************
549 %*                                                                      *
550 \subsection{The @OutputableBndr@ class}
551 %*                                                                      *
552 %************************************************************************
553
554 \begin{code}
555 -- | 'BindingSite' is used to tell the thing that prints binder what
556 -- language construct is binding the identifier.  This can be used
557 -- to decide how much info to print.
558 data BindingSite = LambdaBind | CaseBind | LetBind
559
560 -- | When we print a binder, we often want to print its type too.
561 -- The @OutputableBndr@ class encapsulates this idea.
562 class Outputable a => OutputableBndr a where
563    pprBndr :: BindingSite -> a -> SDoc
564    pprBndr _b x = ppr x
565 \end{code}
566
567 %************************************************************************
568 %*                                                                      *
569 \subsection{Random printing helpers}
570 %*                                                                      *
571 %************************************************************************
572
573 \begin{code}
574 -- We have 31-bit Chars and will simply use Show instances of Char and String.
575
576 -- | Special combinator for showing character literals.
577 pprHsChar :: Char -> SDoc
578 pprHsChar c | c > '\x10ffff' = char '\\' <> text (show (fromIntegral (ord c) :: Word32))
579             | otherwise      = text (show c)
580
581 -- | Special combinator for showing string literals.
582 pprHsString :: FastString -> SDoc
583 pprHsString fs = text (show (unpackFS fs))
584
585 ---------------------
586 -- Put a name in parens if it's an operator
587 pprPrefixVar :: Bool -> SDoc -> SDoc
588 pprPrefixVar is_operator pp_v
589   | is_operator = parens pp_v
590   | otherwise   = pp_v
591
592 -- Put a name in backquotes if it's not an operator
593 pprInfixVar :: Bool -> SDoc -> SDoc
594 pprInfixVar is_operator pp_v 
595   | is_operator = pp_v
596   | otherwise   = char '`' <> pp_v <> char '`'
597
598 ---------------------
599 -- pprHsVar and pprHsInfix use the gruesome isOperator, which
600 -- in turn uses (showSDoc (ppr v)), rather than isSymOcc (getOccName v).
601 -- Reason: it means that pprHsVar doesn't need a NamedThing context,
602 --         which none of the HsSyn printing functions do
603 pprHsVar, pprHsInfix :: Outputable name => name -> SDoc
604 pprHsVar   v = pprPrefixVar (isOperator pp_v) pp_v  
605              where pp_v = ppr v
606 pprHsInfix v = pprInfixVar  (isOperator pp_v) pp_v
607              where pp_v = ppr v
608
609 isOperator :: SDoc -> Bool
610 isOperator ppr_v 
611   = case showSDocUnqual ppr_v of
612         ('(':_)   -> False              -- (), (,) etc
613         ('[':_)   -> False              -- []
614         ('$':c:_) -> not (isAlpha c)    -- Don't treat $d as an operator
615         (':':c:_) -> not (isAlpha c)    -- Don't treat :T as an operator
616         ('_':_)   -> False              -- Not an operator
617         (c:_)     -> not (isAlpha c)    -- Starts with non-alpha
618         _         -> False
619
620 pprFastFilePath :: FastString -> SDoc
621 pprFastFilePath path = text $ normalise $ unpackFS path
622 \end{code}
623
624 %************************************************************************
625 %*                                                                      *
626 \subsection{Other helper functions}
627 %*                                                                      *
628 %************************************************************************
629
630 \begin{code}
631 pprWithCommas :: (a -> SDoc) -- ^ The pretty printing function to use
632               -> [a]         -- ^ The things to be pretty printed
633               -> SDoc        -- ^ 'SDoc' where the things have been pretty printed,
634                              -- comma-separated and finally packed into a paragraph.
635 pprWithCommas pp xs = fsep (punctuate comma (map pp xs))
636
637 -- | Returns the seperated concatenation of the pretty printed things.
638 interppSP  :: Outputable a => [a] -> SDoc
639 interppSP  xs = sep (map ppr xs)
640
641 -- | Returns the comma-seperated concatenation of the pretty printed things.
642 interpp'SP :: Outputable a => [a] -> SDoc
643 interpp'SP xs = sep (punctuate comma (map ppr xs))
644
645 -- | Returns the comma-seperated concatenation of the quoted pretty printed things.
646 --
647 -- > [x,y,z]  ==>  `x', `y', `z'
648 pprQuotedList :: Outputable a => [a] -> SDoc
649 pprQuotedList xs = hsep (punctuate comma (map (quotes . ppr) xs))
650 \end{code}
651
652
653 %************************************************************************
654 %*                                                                      *
655 \subsection{Printing numbers verbally}
656 %*                                                                      *
657 %************************************************************************
658
659 \begin{code}
660 -- | Converts an integer to a verbal index:
661 --
662 -- > speakNth 1 = text "first"
663 -- > speakNth 5 = text "fifth"
664 -- > speakNth 21 = text "21st"
665 speakNth :: Int -> SDoc
666 speakNth 1 = ptext (sLit "first")
667 speakNth 2 = ptext (sLit "second")
668 speakNth 3 = ptext (sLit "third")
669 speakNth 4 = ptext (sLit "fourth")
670 speakNth 5 = ptext (sLit "fifth")
671 speakNth 6 = ptext (sLit "sixth")
672 speakNth n = hcat [ int n, text suffix ]
673   where
674     suffix | n <= 20       = "th"       -- 11,12,13 are non-std
675            | last_dig == 1 = "st"
676            | last_dig == 2 = "nd"
677            | last_dig == 3 = "rd"
678            | otherwise     = "th"
679
680     last_dig = n `rem` 10
681
682 -- | Converts an integer to a verbal multiplicity:
683 -- 
684 -- > speakN 0 = text "none"
685 -- > speakN 5 = text "five"
686 -- > speakN 10 = text "10"
687 speakN :: Int -> SDoc
688 speakN 0 = ptext (sLit "none")  -- E.g.  "he has none"
689 speakN 1 = ptext (sLit "one")   -- E.g.  "he has one"
690 speakN 2 = ptext (sLit "two")
691 speakN 3 = ptext (sLit "three")
692 speakN 4 = ptext (sLit "four")
693 speakN 5 = ptext (sLit "five")
694 speakN 6 = ptext (sLit "six")
695 speakN n = int n
696
697 -- | Converts an integer and object description to a statement about the
698 -- multiplicity of those objects:
699 --
700 -- > speakNOf 0 (text "melon") = text "no melons"
701 -- > speakNOf 1 (text "melon") = text "one melon"
702 -- > speakNOf 3 (text "melon") = text "three melons"
703 speakNOf :: Int -> SDoc -> SDoc
704 speakNOf 0 d = ptext (sLit "no") <+> d <> char 's'
705 speakNOf 1 d = ptext (sLit "one") <+> d                 -- E.g. "one argument"
706 speakNOf n d = speakN n <+> d <> char 's'               -- E.g. "three arguments"
707
708 -- | Converts a strictly positive integer into a number of times:
709 --
710 -- > speakNTimes 1 = text "once"
711 -- > speakNTimes 2 = text "twice"
712 -- > speakNTimes 4 = text "4 times"
713 speakNTimes :: Int {- >=1 -} -> SDoc
714 speakNTimes t | t == 1     = ptext (sLit "once")
715               | t == 2     = ptext (sLit "twice")
716               | otherwise  = speakN t <+> ptext (sLit "times")
717
718 -- | Determines the pluralisation suffix appropriate for the length of a list:
719 --
720 -- > plural [] = char 's'
721 -- > plural ["Hello"] = empty
722 -- > plural ["Hello", "World"] = char 's'
723 plural :: [a] -> SDoc
724 plural [_] = empty  -- a bit frightening, but there you are
725 plural _   = char 's'
726 \end{code}
727
728
729 %************************************************************************
730 %*                                                                      *
731 \subsection{Error handling}
732 %*                                                                      *
733 %************************************************************************
734
735 \begin{code}
736 pprPanic :: String -> SDoc -> a
737 -- ^ Throw an exception saying "bug in GHC"
738 pprPgmError :: String -> SDoc -> a
739 -- ^ Throw an exception saying "bug in pgm being compiled" (used for unusual program errors)
740 pprTrace :: String -> SDoc -> a -> a
741 -- ^ If debug output is on, show some 'SDoc' on the screen
742
743 pprPanic    = pprAndThen panic
744
745 pprPgmError = pprAndThen pgmError
746
747 pprTrace str doc x
748    | opt_NoDebugOutput = x
749    | otherwise         = pprAndThen trace str doc x
750
751 pprPanicFastInt :: String -> SDoc -> FastInt
752 -- ^ Specialization of pprPanic that can be safely used with 'FastInt'
753 pprPanicFastInt heading pretty_msg = panicFastInt (show (doc PprDebug))
754                              where
755                                doc = text heading <+> pretty_msg
756
757 pprAndThen :: (String -> a) -> String -> SDoc -> a
758 pprAndThen cont heading pretty_msg = cont (show (doc PprDebug))
759     where
760      doc = sep [text heading, nest 4 pretty_msg]
761
762 assertPprPanic :: String -> Int -> SDoc -> a
763 -- ^ Panic with an assertation failure, recording the given file and line number.
764 -- Should typically be accessed with the ASSERT family of macros
765 assertPprPanic file line msg
766   = panic (show (doc PprDebug))
767   where
768     doc = sep [hsep[text "ASSERT failed! file", 
769                            text file, 
770                            text "line", int line], 
771                     msg]
772
773 warnPprTrace :: Bool -> String -> Int -> SDoc -> a -> a
774 -- ^ Just warn about an assertion failure, recording the given file and line number.
775 -- Should typically be accessed with the WARN macros
776 warnPprTrace _     _file _line _msg x | opt_NoDebugOutput = x
777 warnPprTrace False _file _line _msg x = x
778 warnPprTrace True   file  line  msg x
779   = trace (show (doc PprDebug)) x
780   where
781     doc = sep [hsep [text "WARNING: file", text file, text "line", int line],
782                msg]
783 \end{code}