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