Remove Control.Parallel*, now in package parallel
[haskell-directory.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 GHC.Base
36 import Data.Maybe
37 import Data.Either
38 import GHC.List ( (!!), foldr1
39 #ifdef USE_REPORT_PRELUDE
40                 , concatMap
41 #endif
42                 )
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 '"' . showl cs
188                  where showl ""       s = showChar '"' s
189                        showl ('"':xs) s = showString "\\\"" (showl xs s)
190                        showl (x:xs)   s = showLitChar x (showl xs s)
191                 -- Making 's' an explicit parameter makes it clear to GHC
192                 -- that showl has arity 2, which avoids it allocating an extra lambda
193                 -- The sticking point is the recursive call to (showl xs), which
194                 -- it can't figure out would be ok with arity 2.
195
196 instance Show Int where
197     showsPrec = showSignedInt
198
199 instance Show a => Show (Maybe a) where
200     showsPrec _p Nothing s = showString "Nothing" s
201     showsPrec p (Just x) s
202                           = (showParen (p > appPrec) $ 
203                              showString "Just " . 
204                              showsPrec appPrec1 x) s
205
206 instance (Show a, Show b) => Show (Either a b) where
207     showsPrec p e s =
208        (showParen (p > appPrec) $
209         case e of
210          Left  a -> showString "Left "  . showsPrec appPrec1 a
211          Right b -> showString "Right " . showsPrec appPrec1 b)
212        s
213 \end{code}
214
215
216 %*********************************************************
217 %*                                                      *
218 \subsection{Show instances for the first few tuples
219 %*                                                      *
220 %*********************************************************
221
222 \begin{code}
223 -- The explicit 's' parameters are important
224 -- Otherwise GHC thinks that "shows x" might take a lot of work to compute
225 -- and generates defns like
226 --      showsPrec _ (x,y) = let sx = shows x; sy = shows y in
227 --                          \s -> showChar '(' (sx (showChar ',' (sy (showChar ')' s))))
228
229 instance  (Show a, Show b) => Show (a,b)  where
230   showsPrec _ (a,b) s = show_tuple [shows a, shows b] s
231
232 instance (Show a, Show b, Show c) => Show (a, b, c) where
233   showsPrec _ (a,b,c) s = show_tuple [shows a, shows b, shows c] s
234
235 instance (Show a, Show b, Show c, Show d) => Show (a, b, c, d) where
236   showsPrec _ (a,b,c,d) s = show_tuple [shows a, shows b, shows c, shows d] s
237
238 instance (Show a, Show b, Show c, Show d, Show e) => Show (a, b, c, d, e) where
239   showsPrec _ (a,b,c,d,e) s = show_tuple [shows a, shows b, shows c, shows d, shows e] s
240
241 instance (Show a, Show b, Show c, Show d, Show e, Show f) => Show (a,b,c,d,e,f) where
242   showsPrec _ (a,b,c,d,e,f) s = show_tuple [shows a, shows b, shows c, shows d, shows e, shows f] s
243
244 instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g)
245         => Show (a,b,c,d,e,f,g) where
246   showsPrec _ (a,b,c,d,e,f,g) s 
247         = show_tuple [shows a, shows b, shows c, shows d, shows e, shows f, shows g] s
248
249 instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h)
250          => Show (a,b,c,d,e,f,g,h) where
251   showsPrec _ (a,b,c,d,e,f,g,h) s 
252         = show_tuple [shows a, shows b, shows c, shows d, shows e, shows f, shows g, shows h] s
253
254 instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i)
255          => Show (a,b,c,d,e,f,g,h,i) where
256   showsPrec _ (a,b,c,d,e,f,g,h,i) s 
257         = show_tuple [shows a, shows b, shows c, shows d, shows e, shows f, shows g, shows h, 
258                       shows i] s
259
260 instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j)
261          => Show (a,b,c,d,e,f,g,h,i,j) where
262   showsPrec _ (a,b,c,d,e,f,g,h,i,j) s 
263         = show_tuple [shows a, shows b, shows c, shows d, shows e, shows f, shows g, shows h, 
264                       shows i, shows j] s
265
266 instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k)
267          => Show (a,b,c,d,e,f,g,h,i,j,k) where
268   showsPrec _ (a,b,c,d,e,f,g,h,i,j,k) s 
269         = show_tuple [shows a, shows b, shows c, shows d, shows e, shows f, shows g, shows h, 
270                       shows i, shows j, shows k] s
271
272 instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k,
273           Show l)
274          => Show (a,b,c,d,e,f,g,h,i,j,k,l) where
275   showsPrec _ (a,b,c,d,e,f,g,h,i,j,k,l) s 
276         = show_tuple [shows a, shows b, shows c, shows d, shows e, shows f, shows g, shows h, 
277                       shows i, shows j, shows k, shows l] s
278
279 instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k,
280           Show l, Show m)
281          => Show (a,b,c,d,e,f,g,h,i,j,k,l,m) where
282   showsPrec _ (a,b,c,d,e,f,g,h,i,j,k,l,m) s 
283         = show_tuple [shows a, shows b, shows c, shows d, shows e, shows f, shows g, shows h, 
284                       shows i, shows j, shows k, shows l, shows m] s
285
286 instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k,
287           Show l, Show m, Show n)
288          => Show (a,b,c,d,e,f,g,h,i,j,k,l,m,n) where
289   showsPrec _ (a,b,c,d,e,f,g,h,i,j,k,l,m,n) s 
290         = show_tuple [shows a, shows b, shows c, shows d, shows e, shows f, shows g, shows h, 
291                       shows i, shows j, shows k, shows l, shows m, shows n] s
292
293 instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k,
294           Show l, Show m, Show n, Show o)
295          => Show (a,b,c,d,e,f,g,h,i,j,k,l,m,n,o) where
296   showsPrec _ (a,b,c,d,e,f,g,h,i,j,k,l,m,n,o) s 
297         = show_tuple [shows a, shows b, shows c, shows d, shows e, shows f, shows g, shows h, 
298                       shows i, shows j, shows k, shows l, shows m, shows n, shows o] s
299
300 show_tuple :: [ShowS] -> ShowS
301 show_tuple ss = showChar '('
302               . foldr1 (\s r -> s . showChar ',' . r) ss
303               . showChar ')'
304 \end{code}
305
306
307 %*********************************************************
308 %*                                                      *
309 \subsection{Support code for @Show@}
310 %*                                                      *
311 %*********************************************************
312
313 \begin{code}
314 -- | equivalent to 'showsPrec' with a precedence of 0.
315 shows           :: (Show a) => a -> ShowS
316 shows           =  showsPrec zeroInt
317
318 -- | utility function converting a 'Char' to a show function that
319 -- simply prepends the character unchanged.
320 showChar        :: Char -> ShowS
321 showChar        =  (:)
322
323 -- | utility function converting a 'String' to a show function that
324 -- simply prepends the string unchanged.
325 showString      :: String -> ShowS
326 showString      =  (++)
327
328 -- | utility function that surrounds the inner show function with
329 -- parentheses when the 'Bool' parameter is 'True'.
330 showParen       :: Bool -> ShowS -> ShowS
331 showParen b p   =  if b then showChar '(' . p . showChar ')' else p
332
333 showSpace :: ShowS
334 showSpace = {-showChar ' '-} \ xs -> ' ' : xs
335 \end{code}
336
337 Code specific for characters
338
339 \begin{code}
340 -- | Convert a character to a string using only printable characters,
341 -- using Haskell source-language escape conventions.  For example:
342 --
343 -- > showLitChar '\n' s  =  "\\n" ++ s
344 --
345 showLitChar                :: Char -> ShowS
346 showLitChar c s | c > '\DEL' =  showChar '\\' (protectEsc isDec (shows (ord c)) s)
347 showLitChar '\DEL'         s =  showString "\\DEL" s
348 showLitChar '\\'           s =  showString "\\\\" s
349 showLitChar c s | c >= ' '   =  showChar c s
350 showLitChar '\a'           s =  showString "\\a" s
351 showLitChar '\b'           s =  showString "\\b" s
352 showLitChar '\f'           s =  showString "\\f" s
353 showLitChar '\n'           s =  showString "\\n" s
354 showLitChar '\r'           s =  showString "\\r" s
355 showLitChar '\t'           s =  showString "\\t" s
356 showLitChar '\v'           s =  showString "\\v" s
357 showLitChar '\SO'          s =  protectEsc (== 'H') (showString "\\SO") s
358 showLitChar c              s =  showString ('\\' : asciiTab!!ord c) s
359         -- I've done manual eta-expansion here, becuase otherwise it's
360         -- impossible to stop (asciiTab!!ord) getting floated out as an MFE
361
362 isDec c = c >= '0' && c <= '9'
363
364 protectEsc :: (Char -> Bool) -> ShowS -> ShowS
365 protectEsc p f             = f . cont
366                              where cont s@(c:_) | p c = "\\&" ++ s
367                                    cont s             = s
368
369
370 asciiTab :: [String]
371 asciiTab = -- Using an array drags in the array module.  listArray ('\NUL', ' ')
372            ["NUL", "SOH", "STX", "ETX", "EOT", "ENQ", "ACK", "BEL",
373             "BS",  "HT",  "LF",  "VT",  "FF",  "CR",  "SO",  "SI", 
374             "DLE", "DC1", "DC2", "DC3", "DC4", "NAK", "SYN", "ETB",
375             "CAN", "EM",  "SUB", "ESC", "FS",  "GS",  "RS",  "US", 
376             "SP"] 
377 \end{code}
378
379 Code specific for Ints.
380
381 \begin{code}
382 -- | Convert an 'Int' in the range @0@..@15@ to the corresponding single
383 -- digit 'Char'.  This function fails on other inputs, and generates
384 -- lower-case hexadecimal digits.
385 intToDigit :: Int -> Char
386 intToDigit (I# i)
387     | i >=# 0#  && i <=#  9# =  unsafeChr (ord '0' `plusInt` I# i)
388     | i >=# 10# && i <=# 15# =  unsafeChr (ord 'a' `minusInt` ten `plusInt` I# i)
389     | otherwise           =  error ("Char.intToDigit: not a digit " ++ show (I# i))
390
391 ten = I# 10#
392
393 showSignedInt :: Int -> Int -> ShowS
394 showSignedInt (I# p) (I# n) r
395     | n <# 0# && p ># 6# = '(' : itos n (')' : r)
396     | otherwise          = itos n r
397
398 itos :: Int# -> String -> String
399 itos n# cs
400     | n# <# 0# =
401         let I# minInt# = minInt in
402         if n# ==# minInt#
403                 -- negateInt# minInt overflows, so we can't do that:
404            then '-' : itos' (negateInt# (n# `quotInt#` 10#))
405                              (itos' (negateInt# (n# `remInt#` 10#)) cs)
406            else '-' : itos' (negateInt# n#) cs
407     | otherwise = itos' n# cs
408     where
409     itos' :: Int# -> String -> String
410     itos' n# cs
411         | n# <# 10#  = C# (chr# (ord# '0'# +# n#)) : cs
412         | otherwise = case chr# (ord# '0'# +# (n# `remInt#` 10#)) of { c# ->
413                       itos' (n# `quotInt#` 10#) (C# c# : cs) }
414 \end{code}