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