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