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