6cb8bf35f71a3945877c97e272024006f98358cb
[ghc-base.git] / GHC / Show.lhs
1 \begin{code}
2 {-# LANGUAGE NoImplicitPrelude, BangPatterns, MagicHash #-}
3 {-# OPTIONS_HADDOCK hide #-}
4
5 -----------------------------------------------------------------------------
6 -- |
7 -- Module      :  GHC.Show
8 -- Copyright   :  (c) The University of Glasgow, 1992-2002
9 -- License     :  see libraries/base/LICENSE
10 -- 
11 -- Maintainer  :  cvs-ghc@haskell.org
12 -- Stability   :  internal
13 -- Portability :  non-portable (GHC Extensions)
14 --
15 -- The 'Show' class, and related operations.
16 --
17 -----------------------------------------------------------------------------
18
19 -- #hide
20 module GHC.Show
21         (
22         Show(..), ShowS,
23
24         -- Instances for Show: (), [], Bool, Ordering, Int, Char
25
26         -- Show support code
27         shows, showChar, showString, showMultiLineString,
28         showParen, showList__, showSpace,
29         showLitChar, showLitString, protectEsc,
30         intToDigit, showSignedInt,
31         appPrec, appPrec1,
32
33         -- Character operations
34         asciiTab,
35   )
36         where
37
38 import GHC.Base
39 import Data.Maybe
40 import GHC.List ((!!), foldr1, break)
41 \end{code}
42
43
44
45 %*********************************************************
46 %*                                                      *
47 \subsection{The @Show@ class}
48 %*                                                      *
49 %*********************************************************
50
51 \begin{code}
52 -- | The @shows@ functions return a function that prepends the
53 -- output 'String' to an existing 'String'.  This allows constant-time
54 -- concatenation of results using function composition.
55 type ShowS = String -> String
56
57 -- | Conversion of values to readable 'String's.
58 --
59 -- Minimal complete definition: 'showsPrec' or 'show'.
60 --
61 -- Derived instances of 'Show' have the following properties, which
62 -- are compatible with derived instances of 'Text.Read.Read':
63 --
64 -- * The result of 'show' is a syntactically correct Haskell
65 --   expression containing only constants, given the fixity
66 --   declarations in force at the point where the type is declared.
67 --   It contains only the constructor names defined in the data type,
68 --   parentheses, and spaces.  When labelled constructor fields are
69 --   used, braces, commas, field names, and equal signs are also used.
70 --
71 -- * If the constructor is defined to be an infix operator, then
72 --   'showsPrec' will produce infix applications of the constructor.
73 --
74 -- * the representation will be enclosed in parentheses if the
75 --   precedence of the top-level constructor in @x@ is less than @d@
76 --   (associativity is ignored).  Thus, if @d@ is @0@ then the result
77 --   is never surrounded in parentheses; if @d@ is @11@ it is always
78 --   surrounded in parentheses, unless it is an atomic expression.
79 --
80 -- * If the constructor is defined using record syntax, then 'show'
81 --   will produce the record-syntax form, with the fields given in the
82 --   same order as the original declaration.
83 --
84 -- For example, given the declarations
85 --
86 -- > infixr 5 :^:
87 -- > data Tree a =  Leaf a  |  Tree a :^: Tree a
88 --
89 -- the derived instance of 'Show' is equivalent to
90 --
91 -- > instance (Show a) => Show (Tree a) where
92 -- >
93 -- >        showsPrec d (Leaf m) = showParen (d > app_prec) $
94 -- >             showString "Leaf " . showsPrec (app_prec+1) m
95 -- >          where app_prec = 10
96 -- >
97 -- >        showsPrec d (u :^: v) = showParen (d > up_prec) $
98 -- >             showsPrec (up_prec+1) u . 
99 -- >             showString " :^: "      .
100 -- >             showsPrec (up_prec+1) v
101 -- >          where up_prec = 5
102 --
103 -- Note that right-associativity of @:^:@ is ignored.  For example,
104 --
105 -- * @'show' (Leaf 1 :^: Leaf 2 :^: Leaf 3)@ produces the string
106 --   @\"Leaf 1 :^: (Leaf 2 :^: Leaf 3)\"@.
107
108 class  Show a  where
109     -- | Convert a value to a readable 'String'.
110     --
111     -- 'showsPrec' should satisfy the law
112     --
113     -- > showsPrec d x r ++ s  ==  showsPrec d x (r ++ s)
114     --
115     -- Derived instances of 'Text.Read.Read' and 'Show' satisfy the following:
116     --
117     -- * @(x,\"\")@ is an element of
118     --   @('Text.Read.readsPrec' d ('showsPrec' d x \"\"))@.
119     --
120     -- That is, 'Text.Read.readsPrec' parses the string produced by
121     -- 'showsPrec', and delivers the value that 'showsPrec' started with.
122
123     showsPrec :: Int    -- ^ the operator precedence of the enclosing
124                         -- context (a number from @0@ to @11@).
125                         -- Function application has precedence @10@.
126               -> a      -- ^ the value to be converted to a 'String'
127               -> ShowS
128
129     -- | A specialised variant of 'showsPrec', using precedence context
130     -- zero, and returning an ordinary 'String'.
131     show      :: a   -> String
132
133     -- | The method 'showList' is provided to allow the programmer to
134     -- give a specialised way of showing lists of values.
135     -- For example, this is used by the predefined 'Show' instance of
136     -- the 'Char' type, where values of type 'String' should be shown
137     -- in double quotes, rather than between square brackets.
138     showList  :: [a] -> ShowS
139
140     showsPrec _ x s = show x ++ s
141     show x          = shows x ""
142     showList ls   s = showList__ shows ls s
143
144 showList__ :: (a -> ShowS) ->  [a] -> ShowS
145 showList__ _     []     s = "[]" ++ s
146 showList__ showx (x:xs) s = '[' : showx x (showl xs)
147   where
148     showl []     = ']' : s
149     showl (y:ys) = ',' : showx y (showl ys)
150
151 appPrec, appPrec1 :: Int
152         -- Use unboxed stuff because we don't have overloaded numerics yet
153 appPrec = I# 10#        -- Precedence of application:
154                         --   one more than the maximum operator precedence of 9
155 appPrec1 = I# 11#       -- appPrec + 1
156 \end{code}
157
158 %*********************************************************
159 %*                                                      *
160 \subsection{Simple Instances}
161 %*                                                      *
162 %*********************************************************
163
164 \begin{code}
165  
166 instance  Show ()  where
167     showsPrec _ () = showString "()"
168
169 instance Show a => Show [a]  where
170     showsPrec _         = showList
171
172 instance Show Bool where
173   showsPrec _ True  = showString "True"
174   showsPrec _ False = showString "False"
175
176 instance Show Ordering where
177   showsPrec _ LT = showString "LT"
178   showsPrec _ EQ = showString "EQ"
179   showsPrec _ GT = showString "GT"
180
181 instance  Show Char  where
182     showsPrec _ '\'' = showString "'\\''"
183     showsPrec _ c    = showChar '\'' . showLitChar c . showChar '\''
184
185     showList cs = showChar '"' . showLitString cs . showChar '"'
186
187 instance Show Int where
188     showsPrec = showSignedInt
189
190 instance Show a => Show (Maybe a) where
191     showsPrec _p Nothing s = showString "Nothing" s
192     showsPrec p (Just x) s
193                           = (showParen (p > appPrec) $ 
194                              showString "Just " . 
195                              showsPrec appPrec1 x) s
196 \end{code}
197
198
199 %*********************************************************
200 %*                                                      *
201 \subsection{Show instances for the first few tuples
202 %*                                                      *
203 %*********************************************************
204
205 \begin{code}
206 -- The explicit 's' parameters are important
207 -- Otherwise GHC thinks that "shows x" might take a lot of work to compute
208 -- and generates defns like
209 --      showsPrec _ (x,y) = let sx = shows x; sy = shows y in
210 --                          \s -> showChar '(' (sx (showChar ',' (sy (showChar ')' s))))
211
212 instance  (Show a, Show b) => Show (a,b)  where
213   showsPrec _ (a,b) s = show_tuple [shows a, shows b] s
214
215 instance (Show a, Show b, Show c) => Show (a, b, c) where
216   showsPrec _ (a,b,c) s = show_tuple [shows a, shows b, shows c] s
217
218 instance (Show a, Show b, Show c, Show d) => Show (a, b, c, d) where
219   showsPrec _ (a,b,c,d) s = show_tuple [shows a, shows b, shows c, shows d] s
220
221 instance (Show a, Show b, Show c, Show d, Show e) => Show (a, b, c, d, e) where
222   showsPrec _ (a,b,c,d,e) s = show_tuple [shows a, shows b, shows c, shows d, shows e] s
223
224 instance (Show a, Show b, Show c, Show d, Show e, Show f) => Show (a,b,c,d,e,f) where
225   showsPrec _ (a,b,c,d,e,f) s = show_tuple [shows a, shows b, shows c, shows d, shows e, shows f] s
226
227 instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g)
228         => Show (a,b,c,d,e,f,g) where
229   showsPrec _ (a,b,c,d,e,f,g) s 
230         = show_tuple [shows a, shows b, shows c, shows d, shows e, shows f, shows g] s
231
232 instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h)
233          => Show (a,b,c,d,e,f,g,h) where
234   showsPrec _ (a,b,c,d,e,f,g,h) s 
235         = show_tuple [shows a, shows b, shows c, shows d, shows e, shows f, shows g, shows h] s
236
237 instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i)
238          => Show (a,b,c,d,e,f,g,h,i) where
239   showsPrec _ (a,b,c,d,e,f,g,h,i) s 
240         = show_tuple [shows a, shows b, shows c, shows d, shows e, shows f, shows g, shows h, 
241                       shows i] s
242
243 instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j)
244          => Show (a,b,c,d,e,f,g,h,i,j) where
245   showsPrec _ (a,b,c,d,e,f,g,h,i,j) s 
246         = show_tuple [shows a, shows b, shows c, shows d, shows e, shows f, shows g, shows h, 
247                       shows i, shows j] s
248
249 instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k)
250          => Show (a,b,c,d,e,f,g,h,i,j,k) where
251   showsPrec _ (a,b,c,d,e,f,g,h,i,j,k) s 
252         = show_tuple [shows a, shows b, shows c, shows d, shows e, shows f, shows g, shows h, 
253                       shows i, shows j, shows k] s
254
255 instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k,
256           Show l)
257          => Show (a,b,c,d,e,f,g,h,i,j,k,l) where
258   showsPrec _ (a,b,c,d,e,f,g,h,i,j,k,l) s 
259         = show_tuple [shows a, shows b, shows c, shows d, shows e, shows f, shows g, shows h, 
260                       shows i, shows j, shows k, shows l] s
261
262 instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k,
263           Show l, Show m)
264          => Show (a,b,c,d,e,f,g,h,i,j,k,l,m) where
265   showsPrec _ (a,b,c,d,e,f,g,h,i,j,k,l,m) s 
266         = show_tuple [shows a, shows b, shows c, shows d, shows e, shows f, shows g, shows h, 
267                       shows i, shows j, shows k, shows l, shows m] s
268
269 instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k,
270           Show l, Show m, Show n)
271          => Show (a,b,c,d,e,f,g,h,i,j,k,l,m,n) where
272   showsPrec _ (a,b,c,d,e,f,g,h,i,j,k,l,m,n) s 
273         = show_tuple [shows a, shows b, shows c, shows d, shows e, shows f, shows g, shows h, 
274                       shows i, shows j, shows k, shows l, shows m, shows n] s
275
276 instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k,
277           Show l, Show m, Show n, Show o)
278          => Show (a,b,c,d,e,f,g,h,i,j,k,l,m,n,o) where
279   showsPrec _ (a,b,c,d,e,f,g,h,i,j,k,l,m,n,o) s 
280         = show_tuple [shows a, shows b, shows c, shows d, shows e, shows f, shows g, shows h, 
281                       shows i, shows j, shows k, shows l, shows m, shows n, shows o] s
282
283 show_tuple :: [ShowS] -> ShowS
284 show_tuple ss = showChar '('
285               . foldr1 (\s r -> s . showChar ',' . r) ss
286               . showChar ')'
287 \end{code}
288
289
290 %*********************************************************
291 %*                                                      *
292 \subsection{Support code for @Show@}
293 %*                                                      *
294 %*********************************************************
295
296 \begin{code}
297 -- | equivalent to 'showsPrec' with a precedence of 0.
298 shows           :: (Show a) => a -> ShowS
299 shows           =  showsPrec zeroInt
300
301 -- | utility function converting a 'Char' to a show function that
302 -- simply prepends the character unchanged.
303 showChar        :: Char -> ShowS
304 showChar        =  (:)
305
306 -- | utility function converting a 'String' to a show function that
307 -- simply prepends the string unchanged.
308 showString      :: String -> ShowS
309 showString      =  (++)
310
311 -- | utility function that surrounds the inner show function with
312 -- parentheses when the 'Bool' parameter is 'True'.
313 showParen       :: Bool -> ShowS -> ShowS
314 showParen b p   =  if b then showChar '(' . p . showChar ')' else p
315
316 showSpace :: ShowS
317 showSpace = {-showChar ' '-} \ xs -> ' ' : xs
318 \end{code}
319
320 Code specific for characters
321
322 \begin{code}
323 -- | Convert a character to a string using only printable characters,
324 -- using Haskell source-language escape conventions.  For example:
325 --
326 -- > showLitChar '\n' s  =  "\\n" ++ s
327 --
328 showLitChar                :: Char -> ShowS
329 showLitChar c s | c > '\DEL' =  showChar '\\' (protectEsc isDec (shows (ord c)) s)
330 showLitChar '\DEL'         s =  showString "\\DEL" s
331 showLitChar '\\'           s =  showString "\\\\" s
332 showLitChar c s | c >= ' '   =  showChar c s
333 showLitChar '\a'           s =  showString "\\a" s
334 showLitChar '\b'           s =  showString "\\b" s
335 showLitChar '\f'           s =  showString "\\f" s
336 showLitChar '\n'           s =  showString "\\n" s
337 showLitChar '\r'           s =  showString "\\r" s
338 showLitChar '\t'           s =  showString "\\t" s
339 showLitChar '\v'           s =  showString "\\v" s
340 showLitChar '\SO'          s =  protectEsc (== 'H') (showString "\\SO") s
341 showLitChar c              s =  showString ('\\' : asciiTab!!ord c) s
342         -- I've done manual eta-expansion here, becuase otherwise it's
343         -- impossible to stop (asciiTab!!ord) getting floated out as an MFE
344
345 showLitString :: String -> ShowS
346 -- | Same as 'showLitChar', but for strings
347 -- It converts the string to a string using Haskell escape conventions
348 -- for non-printable characters. Does not add double-quotes around the
349 -- whole thing; the caller should do that.
350 -- The main difference from showLitChar (apart from the fact that the
351 -- argument is a string not a list) is that we must escape double-quotes 
352 showLitString []         s = s
353 showLitString ('"' : cs) s = showString "\\\"" (showLitString cs s)
354 showLitString (c   : cs) s = showLitChar c (showLitString cs s)
355    -- Making 's' an explicit parameter makes it clear to GHC that
356    -- showLitString has arity 2, which avoids it allocating an extra lambda
357    -- The sticking point is the recursive call to (showLitString cs), which
358    -- it can't figure out would be ok with arity 2.
359
360 showMultiLineString :: String -> [String]
361 -- | Like 'showLitString' (expand escape characters using Haskell
362 -- escape conventions), but 
363 --   * break the string into multiple lines
364 --   * wrap the entire thing in double quotes
365 -- Example:  @breakMultiLineString "hello\ngoodbye\nblah"@ 
366 -- returns   @["\"hello\\", "\\goodbye\\", "\\blah\"" ]@
367 -- where those "\\" are really just a single backslash
368 -- (but I'm writing them here as Haskell literals)
369 showMultiLineString str
370   = go '\"' str
371   where
372     go ch s = case break (== '\n') s of
373                 (l, _:s'@(_:_)) -> (ch : showLitString l "\\") : go '\\' s'
374                 (l, _)          -> [ch : showLitString l "\""]
375
376 isDec :: Char -> Bool
377 isDec c = c >= '0' && c <= '9'
378
379 protectEsc :: (Char -> Bool) -> ShowS -> ShowS
380 protectEsc p f             = f . cont
381                              where cont s@(c:_) | p c = "\\&" ++ s
382                                    cont s             = s
383
384
385 asciiTab :: [String]
386 asciiTab = -- Using an array drags in the array module.  listArray ('\NUL', ' ')
387            ["NUL", "SOH", "STX", "ETX", "EOT", "ENQ", "ACK", "BEL",
388             "BS",  "HT",  "LF",  "VT",  "FF",  "CR",  "SO",  "SI", 
389             "DLE", "DC1", "DC2", "DC3", "DC4", "NAK", "SYN", "ETB",
390             "CAN", "EM",  "SUB", "ESC", "FS",  "GS",  "RS",  "US", 
391             "SP"] 
392 \end{code}
393
394 Code specific for Ints.
395
396 \begin{code}
397 -- | Convert an 'Int' in the range @0@..@15@ to the corresponding single
398 -- digit 'Char'.  This function fails on other inputs, and generates
399 -- lower-case hexadecimal digits.
400 intToDigit :: Int -> Char
401 intToDigit (I# i)
402     | i >=# 0#  && i <=#  9# =  unsafeChr (ord '0' `plusInt` I# i)
403     | i >=# 10# && i <=# 15# =  unsafeChr (ord 'a' `minusInt` ten `plusInt` I# i)
404     | otherwise           =  error ("Char.intToDigit: not a digit " ++ show (I# i))
405
406 ten :: Int
407 ten = I# 10#
408
409 showSignedInt :: Int -> Int -> ShowS
410 showSignedInt (I# p) (I# n) r
411     | n <# 0# && p ># 6# = '(' : itos n (')' : r)
412     | otherwise          = itos n r
413
414 itos :: Int# -> String -> String
415 itos n# cs
416     | n# <# 0# =
417         let !(I# minInt#) = minInt in
418         if n# ==# minInt#
419                 -- negateInt# minInt overflows, so we can't do that:
420            then '-' : itos' (negateInt# (n# `quotInt#` 10#))
421                              (itos' (negateInt# (n# `remInt#` 10#)) cs)
422            else '-' : itos' (negateInt# n#) cs
423     | otherwise = itos' n# cs
424     where
425     itos' :: Int# -> String -> String
426     itos' x# cs'
427         | x# <# 10#  = C# (chr# (ord# '0'# +# x#)) : cs'
428         | otherwise = case chr# (ord# '0'# +# (x# `remInt#` 10#)) of { c# ->
429                       itos' (x# `quotInt#` 10#) (C# c# : cs') }
430 \end{code}
431