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