add GHC.HetMet.{hetmet_kappa,hetmet_kappa_app}
[ghc-base.git] / GHC / Show.lhs
1 \begin{code}
2 {-# LANGUAGE NoImplicitPrelude, BangPatterns, MagicHash, StandaloneDeriving #-}
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 -- For defining instances for the generic deriving mechanism
42 import GHC.Generics (Arity(..), Associativity(..), Fixity(..))
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 '"' . showLitString cs . showChar '"'
188
189 instance Show Int where
190     showsPrec = showSignedInt
191
192 instance Show a => Show (Maybe a) where
193     showsPrec _p Nothing s = showString "Nothing" s
194     showsPrec p (Just x) s
195                           = (showParen (p > appPrec) $ 
196                              showString "Just " . 
197                              showsPrec appPrec1 x) s
198 \end{code}
199
200
201 %*********************************************************
202 %*                                                      *
203 \subsection{Show instances for the first few tuples
204 %*                                                      *
205 %*********************************************************
206
207 \begin{code}
208 -- The explicit 's' parameters are important
209 -- Otherwise GHC thinks that "shows x" might take a lot of work to compute
210 -- and generates defns like
211 --      showsPrec _ (x,y) = let sx = shows x; sy = shows y in
212 --                          \s -> showChar '(' (sx (showChar ',' (sy (showChar ')' s))))
213
214 instance  (Show a, Show b) => Show (a,b)  where
215   showsPrec _ (a,b) s = show_tuple [shows a, shows b] s
216
217 instance (Show a, Show b, Show c) => Show (a, b, c) where
218   showsPrec _ (a,b,c) s = show_tuple [shows a, shows b, shows c] s
219
220 instance (Show a, Show b, Show c, Show d) => Show (a, b, c, d) where
221   showsPrec _ (a,b,c,d) s = show_tuple [shows a, shows b, shows c, shows d] s
222
223 instance (Show a, Show b, Show c, Show d, Show e) => Show (a, b, c, d, e) where
224   showsPrec _ (a,b,c,d,e) s = show_tuple [shows a, shows b, shows c, shows d, shows e] s
225
226 instance (Show a, Show b, Show c, Show d, Show e, Show f) => Show (a,b,c,d,e,f) where
227   showsPrec _ (a,b,c,d,e,f) s = show_tuple [shows a, shows b, shows c, shows d, shows e, shows f] s
228
229 instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g)
230         => Show (a,b,c,d,e,f,g) where
231   showsPrec _ (a,b,c,d,e,f,g) s 
232         = show_tuple [shows a, shows b, shows c, shows d, shows e, shows f, shows g] s
233
234 instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h)
235          => Show (a,b,c,d,e,f,g,h) where
236   showsPrec _ (a,b,c,d,e,f,g,h) s 
237         = show_tuple [shows a, shows b, shows c, shows d, shows e, shows f, shows g, shows h] s
238
239 instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i)
240          => Show (a,b,c,d,e,f,g,h,i) where
241   showsPrec _ (a,b,c,d,e,f,g,h,i) s 
242         = show_tuple [shows a, shows b, shows c, shows d, shows e, shows f, shows g, shows h, 
243                       shows i] s
244
245 instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j)
246          => Show (a,b,c,d,e,f,g,h,i,j) where
247   showsPrec _ (a,b,c,d,e,f,g,h,i,j) s 
248         = show_tuple [shows a, shows b, shows c, shows d, shows e, shows f, shows g, shows h, 
249                       shows i, shows j] s
250
251 instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k)
252          => Show (a,b,c,d,e,f,g,h,i,j,k) where
253   showsPrec _ (a,b,c,d,e,f,g,h,i,j,k) s 
254         = show_tuple [shows a, shows b, shows c, shows d, shows e, shows f, shows g, shows h, 
255                       shows i, shows j, shows k] s
256
257 instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k,
258           Show l)
259          => Show (a,b,c,d,e,f,g,h,i,j,k,l) where
260   showsPrec _ (a,b,c,d,e,f,g,h,i,j,k,l) 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, shows l] 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, Show m)
266          => Show (a,b,c,d,e,f,g,h,i,j,k,l,m) where
267   showsPrec _ (a,b,c,d,e,f,g,h,i,j,k,l,m) 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, shows m] 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, Show n)
273          => Show (a,b,c,d,e,f,g,h,i,j,k,l,m,n) where
274   showsPrec _ (a,b,c,d,e,f,g,h,i,j,k,l,m,n) 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, shows n] 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, Show o)
280          => Show (a,b,c,d,e,f,g,h,i,j,k,l,m,n,o) where
281   showsPrec _ (a,b,c,d,e,f,g,h,i,j,k,l,m,n,o) 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, shows o] s
284
285 show_tuple :: [ShowS] -> ShowS
286 show_tuple ss = showChar '('
287               . foldr1 (\s r -> s . showChar ',' . r) ss
288               . showChar ')'
289 \end{code}
290
291
292 %*********************************************************
293 %*                                                      *
294 \subsection{Support code for @Show@}
295 %*                                                      *
296 %*********************************************************
297
298 \begin{code}
299 -- | equivalent to 'showsPrec' with a precedence of 0.
300 shows           :: (Show a) => a -> ShowS
301 shows           =  showsPrec zeroInt
302
303 -- | utility function converting a 'Char' to a show function that
304 -- simply prepends the character unchanged.
305 showChar        :: Char -> ShowS
306 showChar        =  (:)
307
308 -- | utility function converting a 'String' to a show function that
309 -- simply prepends the string unchanged.
310 showString      :: String -> ShowS
311 showString      =  (++)
312
313 -- | utility function that surrounds the inner show function with
314 -- parentheses when the 'Bool' parameter is 'True'.
315 showParen       :: Bool -> ShowS -> ShowS
316 showParen b p   =  if b then showChar '(' . p . showChar ')' else p
317
318 showSpace :: ShowS
319 showSpace = {-showChar ' '-} \ xs -> ' ' : xs
320 \end{code}
321
322 Code specific for characters
323
324 \begin{code}
325 -- | Convert a character to a string using only printable characters,
326 -- using Haskell source-language escape conventions.  For example:
327 --
328 -- > showLitChar '\n' s  =  "\\n" ++ s
329 --
330 showLitChar                :: Char -> ShowS
331 showLitChar c s | c > '\DEL' =  showChar '\\' (protectEsc isDec (shows (ord c)) s)
332 showLitChar '\DEL'         s =  showString "\\DEL" s
333 showLitChar '\\'           s =  showString "\\\\" s
334 showLitChar c s | c >= ' '   =  showChar c s
335 showLitChar '\a'           s =  showString "\\a" s
336 showLitChar '\b'           s =  showString "\\b" s
337 showLitChar '\f'           s =  showString "\\f" s
338 showLitChar '\n'           s =  showString "\\n" s
339 showLitChar '\r'           s =  showString "\\r" s
340 showLitChar '\t'           s =  showString "\\t" s
341 showLitChar '\v'           s =  showString "\\v" s
342 showLitChar '\SO'          s =  protectEsc (== 'H') (showString "\\SO") s
343 showLitChar c              s =  showString ('\\' : asciiTab!!ord c) s
344         -- I've done manual eta-expansion here, becuase otherwise it's
345         -- impossible to stop (asciiTab!!ord) getting floated out as an MFE
346
347 showLitString :: String -> ShowS
348 -- | Same as 'showLitChar', but for strings
349 -- It converts the string to a string using Haskell escape conventions
350 -- for non-printable characters. Does not add double-quotes around the
351 -- whole thing; the caller should do that.
352 -- The main difference from showLitChar (apart from the fact that the
353 -- argument is a string not a list) is that we must escape double-quotes 
354 showLitString []         s = s
355 showLitString ('"' : cs) s = showString "\\\"" (showLitString cs s)
356 showLitString (c   : cs) s = showLitChar c (showLitString cs s)
357    -- Making 's' an explicit parameter makes it clear to GHC that
358    -- showLitString has arity 2, which avoids it allocating an extra lambda
359    -- The sticking point is the recursive call to (showLitString cs), which
360    -- it can't figure out would be ok with arity 2.
361
362 showMultiLineString :: String -> [String]
363 -- | Like 'showLitString' (expand escape characters using Haskell
364 -- escape conventions), but 
365 --   * break the string into multiple lines
366 --   * wrap the entire thing in double quotes
367 -- Example:  @breakMultiLineString "hello\ngoodbye\nblah"@ 
368 -- returns   @["\"hello\\", "\\goodbye\\", "\\blah\"" ]@
369 -- where those "\\" are really just a single backslash
370 -- (but I'm writing them here as Haskell literals)
371 showMultiLineString str
372   = go '\"' str
373   where
374     go ch s = case break (== '\n') s of
375                 (l, _:s'@(_:_)) -> (ch : showLitString l "\\") : go '\\' s'
376                 (l, _)          -> [ch : showLitString l "\""]
377
378 isDec :: Char -> Bool
379 isDec c = c >= '0' && c <= '9'
380
381 protectEsc :: (Char -> Bool) -> ShowS -> ShowS
382 protectEsc p f             = f . cont
383                              where cont s@(c:_) | p c = "\\&" ++ s
384                                    cont s             = s
385
386
387 asciiTab :: [String]
388 asciiTab = -- Using an array drags in the array module.  listArray ('\NUL', ' ')
389            ["NUL", "SOH", "STX", "ETX", "EOT", "ENQ", "ACK", "BEL",
390             "BS",  "HT",  "LF",  "VT",  "FF",  "CR",  "SO",  "SI", 
391             "DLE", "DC1", "DC2", "DC3", "DC4", "NAK", "SYN", "ETB",
392             "CAN", "EM",  "SUB", "ESC", "FS",  "GS",  "RS",  "US", 
393             "SP"] 
394 \end{code}
395
396 Code specific for Ints.
397
398 \begin{code}
399 -- | Convert an 'Int' in the range @0@..@15@ to the corresponding single
400 -- digit 'Char'.  This function fails on other inputs, and generates
401 -- lower-case hexadecimal digits.
402 intToDigit :: Int -> Char
403 intToDigit (I# i)
404     | i >=# 0#  && i <=#  9# =  unsafeChr (ord '0' `plusInt` I# i)
405     | i >=# 10# && i <=# 15# =  unsafeChr (ord 'a' `minusInt` ten `plusInt` I# i)
406     | otherwise           =  error ("Char.intToDigit: not a digit " ++ show (I# i))
407
408 ten :: Int
409 ten = I# 10#
410
411 showSignedInt :: Int -> Int -> ShowS
412 showSignedInt (I# p) (I# n) r
413     | n <# 0# && p ># 6# = '(' : itos n (')' : r)
414     | otherwise          = itos n r
415
416 itos :: Int# -> String -> String
417 itos n# cs
418     | n# <# 0# =
419         let !(I# minInt#) = minInt in
420         if n# ==# minInt#
421                 -- negateInt# minInt overflows, so we can't do that:
422            then '-' : itos' (negateInt# (n# `quotInt#` 10#))
423                              (itos' (negateInt# (n# `remInt#` 10#)) cs)
424            else '-' : itos' (negateInt# n#) cs
425     | otherwise = itos' n# cs
426     where
427     itos' :: Int# -> String -> String
428     itos' x# cs'
429         | x# <# 10#  = C# (chr# (ord# '0'# +# x#)) : cs'
430         | otherwise = case chr# (ord# '0'# +# (x# `remInt#` 10#)) of { c# ->
431                       itos' (x# `quotInt#` 10#) (C# c# : cs') }
432 \end{code}
433
434 Instances for types of the generic deriving mechanism.
435
436 \begin{code}
437 deriving instance Show Arity
438 deriving instance Show Associativity
439 deriving instance Show Fixity
440 \end{code}