add GHC.HetMet.{hetmet_kappa,hetmet_kappa_app}
[ghc-base.git] / GHC / Read.lhs
1 \begin{code}
2 {-# LANGUAGE CPP, NoImplicitPrelude, StandaloneDeriving #-}
3 {-# OPTIONS_HADDOCK hide #-}
4
5 -----------------------------------------------------------------------------
6 -- |
7 -- Module      :  GHC.Read
8 -- Copyright   :  (c) The University of Glasgow, 1994-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 'Read' class and instances for basic data types.
16 --
17 -----------------------------------------------------------------------------
18
19 -- #hide
20 module GHC.Read
21   ( Read(..)   -- class
22
23   -- ReadS type
24   , ReadS      -- :: *; = String -> [(a,String)]
25
26   -- H98 compatibility
27   , lex         -- :: ReadS String
28   , lexLitChar  -- :: ReadS String
29   , readLitChar -- :: ReadS Char
30   , lexDigits   -- :: ReadS String
31
32   -- defining readers
33   , lexP       -- :: ReadPrec Lexeme
34   , paren      -- :: ReadPrec a -> ReadPrec a
35   , parens     -- :: ReadPrec a -> ReadPrec a
36   , list       -- :: ReadPrec a -> ReadPrec [a]
37   , choose     -- :: [(String, ReadPrec a)] -> ReadPrec a
38   , readListDefault, readListPrecDefault
39
40   -- Temporary
41   , readParen
42
43   -- XXX Can this be removed?
44   , readp
45   )
46  where
47
48 import qualified Text.ParserCombinators.ReadP as P
49
50 import Text.ParserCombinators.ReadP
51   ( ReadP
52   , ReadS
53   , readP_to_S
54   )
55
56 import qualified Text.Read.Lex as L
57 -- Lex exports 'lex', which is also defined here,
58 -- hence the qualified import.
59 -- We can't import *anything* unqualified, because that
60 -- confuses Haddock.
61
62 import Text.ParserCombinators.ReadPrec
63
64 import Data.Maybe
65
66 #ifndef __HADDOCK__
67 import {-# SOURCE #-} GHC.Unicode       ( isDigit )
68 #endif
69 import GHC.Num
70 import GHC.Real
71 import GHC.Float ()
72 import GHC.Show
73 import GHC.Base
74 import GHC.Arr
75 -- For defining instances for the generic deriving mechanism
76 import GHC.Generics (Arity(..), Associativity(..), Fixity(..))
77 \end{code}
78
79
80 \begin{code}
81 -- | @'readParen' 'True' p@ parses what @p@ parses, but surrounded with
82 -- parentheses.
83 --
84 -- @'readParen' 'False' p@ parses what @p@ parses, but optionally
85 -- surrounded with parentheses.
86 readParen       :: Bool -> ReadS a -> ReadS a
87 -- A Haskell 98 function
88 readParen b g   =  if b then mandatory else optional
89                    where optional r  = g r ++ mandatory r
90                          mandatory r = do
91                                 ("(",s) <- lex r
92                                 (x,t)   <- optional s
93                                 (")",u) <- lex t
94                                 return (x,u)
95 \end{code}
96
97
98 %*********************************************************
99 %*                                                      *
100 \subsection{The @Read@ class}
101 %*                                                      *
102 %*********************************************************
103
104 \begin{code}
105 ------------------------------------------------------------------------
106 -- class Read
107
108 -- | Parsing of 'String's, producing values.
109 --
110 -- Minimal complete definition: 'readsPrec' (or, for GHC only, 'readPrec')
111 --
112 -- Derived instances of 'Read' make the following assumptions, which
113 -- derived instances of 'Text.Show.Show' obey:
114 --
115 -- * If the constructor is defined to be an infix operator, then the
116 --   derived 'Read' instance will parse only infix applications of
117 --   the constructor (not the prefix form).
118 --
119 -- * Associativity is not used to reduce the occurrence of parentheses,
120 --   although precedence may be.
121 --
122 -- * If the constructor is defined using record syntax, the derived 'Read'
123 --   will parse only the record-syntax form, and furthermore, the fields
124 --   must be given in the same order as the original declaration.
125 --
126 -- * The derived 'Read' instance allows arbitrary Haskell whitespace
127 --   between tokens of the input string.  Extra parentheses are also
128 --   allowed.
129 --
130 -- For example, given the declarations
131 --
132 -- > infixr 5 :^:
133 -- > data Tree a =  Leaf a  |  Tree a :^: Tree a
134 --
135 -- the derived instance of 'Read' in Haskell 98 is equivalent to
136 --
137 -- > instance (Read a) => Read (Tree a) where
138 -- >
139 -- >         readsPrec d r =  readParen (d > app_prec)
140 -- >                          (\r -> [(Leaf m,t) |
141 -- >                                  ("Leaf",s) <- lex r,
142 -- >                                  (m,t) <- readsPrec (app_prec+1) s]) r
143 -- >
144 -- >                       ++ readParen (d > up_prec)
145 -- >                          (\r -> [(u:^:v,w) |
146 -- >                                  (u,s) <- readsPrec (up_prec+1) r,
147 -- >                                  (":^:",t) <- lex s,
148 -- >                                  (v,w) <- readsPrec (up_prec+1) t]) r
149 -- >
150 -- >           where app_prec = 10
151 -- >                 up_prec = 5
152 --
153 -- Note that right-associativity of @:^:@ is unused.
154 --
155 -- The derived instance in GHC is equivalent to
156 --
157 -- > instance (Read a) => Read (Tree a) where
158 -- >
159 -- >         readPrec = parens $ (prec app_prec $ do
160 -- >                                  Ident "Leaf" <- lexP
161 -- >                                  m <- step readPrec
162 -- >                                  return (Leaf m))
163 -- >
164 -- >                      +++ (prec up_prec $ do
165 -- >                                  u <- step readPrec
166 -- >                                  Symbol ":^:" <- lexP
167 -- >                                  v <- step readPrec
168 -- >                                  return (u :^: v))
169 -- >
170 -- >           where app_prec = 10
171 -- >                 up_prec = 5
172 -- >
173 -- >         readListPrec = readListPrecDefault
174
175 class Read a where
176   -- | attempts to parse a value from the front of the string, returning
177   -- a list of (parsed value, remaining string) pairs.  If there is no
178   -- successful parse, the returned list is empty.
179   --
180   -- Derived instances of 'Read' and 'Text.Show.Show' satisfy the following:
181   --
182   -- * @(x,\"\")@ is an element of
183   --   @('readsPrec' d ('Text.Show.showsPrec' d x \"\"))@.
184   --
185   -- That is, 'readsPrec' parses the string produced by
186   -- 'Text.Show.showsPrec', and delivers the value that
187   -- 'Text.Show.showsPrec' started with.
188
189   readsPrec    :: Int   -- ^ the operator precedence of the enclosing
190                         -- context (a number from @0@ to @11@).
191                         -- Function application has precedence @10@.
192                 -> ReadS a
193
194   -- | The method 'readList' is provided to allow the programmer to
195   -- give a specialised way of parsing lists of values.
196   -- For example, this is used by the predefined 'Read' instance of
197   -- the 'Char' type, where values of type 'String' should be are
198   -- expected to use double quotes, rather than square brackets.
199   readList     :: ReadS [a]
200
201   -- | Proposed replacement for 'readsPrec' using new-style parsers (GHC only).
202   readPrec     :: ReadPrec a
203
204   -- | Proposed replacement for 'readList' using new-style parsers (GHC only).
205   -- The default definition uses 'readList'.  Instances that define 'readPrec'
206   -- should also define 'readListPrec' as 'readListPrecDefault'.
207   readListPrec :: ReadPrec [a]
208   
209   -- default definitions
210   readsPrec    = readPrec_to_S readPrec
211   readList     = readPrec_to_S (list readPrec) 0
212   readPrec     = readS_to_Prec readsPrec
213   readListPrec = readS_to_Prec (\_ -> readList)
214
215 readListDefault :: Read a => ReadS [a]
216 -- ^ A possible replacement definition for the 'readList' method (GHC only).
217 --   This is only needed for GHC, and even then only for 'Read' instances
218 --   where 'readListPrec' isn't defined as 'readListPrecDefault'.
219 readListDefault = readPrec_to_S readListPrec 0
220
221 readListPrecDefault :: Read a => ReadPrec [a]
222 -- ^ A possible replacement definition for the 'readListPrec' method,
223 --   defined using 'readPrec' (GHC only).
224 readListPrecDefault = list readPrec
225
226 ------------------------------------------------------------------------
227 -- H98 compatibility
228
229 -- | The 'lex' function reads a single lexeme from the input, discarding
230 -- initial white space, and returning the characters that constitute the
231 -- lexeme.  If the input string contains only white space, 'lex' returns a
232 -- single successful \`lexeme\' consisting of the empty string.  (Thus
233 -- @'lex' \"\" = [(\"\",\"\")]@.)  If there is no legal lexeme at the
234 -- beginning of the input string, 'lex' fails (i.e. returns @[]@).
235 --
236 -- This lexer is not completely faithful to the Haskell lexical syntax
237 -- in the following respects:
238 --
239 -- * Qualified names are not handled properly
240 --
241 -- * Octal and hexadecimal numerics are not recognized as a single token
242 --
243 -- * Comments are not treated properly
244 lex :: ReadS String             -- As defined by H98
245 lex s  = readP_to_S L.hsLex s
246
247 -- | Read a string representation of a character, using Haskell
248 -- source-language escape conventions.  For example:
249 --
250 -- > lexLitChar  "\\nHello"  =  [("\\n", "Hello")]
251 --
252 lexLitChar :: ReadS String      -- As defined by H98
253 lexLitChar = readP_to_S (do { (s, _) <- P.gather L.lexChar ;
254                               return s })
255         -- There was a skipSpaces before the P.gather L.lexChar,
256         -- but that seems inconsistent with readLitChar
257
258 -- | Read a string representation of a character, using Haskell
259 -- source-language escape conventions, and convert it to the character
260 -- that it encodes.  For example:
261 --
262 -- > readLitChar "\\nHello"  =  [('\n', "Hello")]
263 --
264 readLitChar :: ReadS Char       -- As defined by H98
265 readLitChar = readP_to_S L.lexChar
266
267 -- | Reads a non-empty string of decimal digits.
268 lexDigits :: ReadS String
269 lexDigits = readP_to_S (P.munch1 isDigit)
270
271 ------------------------------------------------------------------------
272 -- utility parsers
273
274 lexP :: ReadPrec L.Lexeme
275 -- ^ Parse a single lexeme
276 lexP = lift L.lex
277
278 paren :: ReadPrec a -> ReadPrec a
279 -- ^ @(paren p)@ parses \"(P0)\"
280 --      where @p@ parses \"P0\" in precedence context zero
281 paren p = do L.Punc "(" <- lexP
282              x          <- reset p
283              L.Punc ")" <- lexP
284              return x
285
286 parens :: ReadPrec a -> ReadPrec a
287 -- ^ @(parens p)@ parses \"P\", \"(P0)\", \"((P0))\", etc, 
288 --      where @p@ parses \"P\"  in the current precedence context
289 --          and parses \"P0\" in precedence context zero
290 parens p = optional
291  where
292   optional  = p +++ mandatory
293   mandatory = paren optional
294
295 list :: ReadPrec a -> ReadPrec [a]
296 -- ^ @(list p)@ parses a list of things parsed by @p@,
297 -- using the usual square-bracket syntax.
298 list readx =
299   parens
300   ( do L.Punc "[" <- lexP
301        (listRest False +++ listNext)
302   )
303  where
304   listRest started =
305     do L.Punc c <- lexP
306        case c of
307          "]"           -> return []
308          "," | started -> listNext
309          _             -> pfail
310   
311   listNext =
312     do x  <- reset readx
313        xs <- listRest True
314        return (x:xs)
315
316 choose :: [(String, ReadPrec a)] -> ReadPrec a
317 -- ^ Parse the specified lexeme and continue as specified.
318 -- Esp useful for nullary constructors; e.g.
319 --    @choose [(\"A\", return A), (\"B\", return B)]@
320 -- We match both Ident and Symbol because the constructor
321 -- might be an operator eg (:=:)
322 choose sps = foldr ((+++) . try_one) pfail sps
323            where
324              try_one (s,p) = do { token <- lexP ;
325                                   case token of
326                                     L.Ident s'  | s==s' -> p
327                                     L.Symbol s' | s==s' -> p
328                                     _other              -> pfail }
329 \end{code}
330
331
332 %*********************************************************
333 %*                                                      *
334 \subsection{Simple instances of Read}
335 %*                                                      *
336 %*********************************************************
337
338 \begin{code}
339 instance Read Char where
340   readPrec =
341     parens
342     ( do L.Char c <- lexP
343          return c
344     )
345
346   readListPrec =
347     parens
348     ( do L.String s <- lexP     -- Looks for "foo"
349          return s
350      +++
351       readListPrecDefault       -- Looks for ['f','o','o']
352     )                           -- (more generous than H98 spec)
353
354   readList = readListDefault
355
356 instance Read Bool where
357   readPrec =
358     parens
359     ( do L.Ident s <- lexP
360          case s of
361            "True"  -> return True
362            "False" -> return False
363            _       -> pfail
364     )
365
366   readListPrec = readListPrecDefault
367   readList     = readListDefault
368
369 instance Read Ordering where
370   readPrec =
371     parens
372     ( do L.Ident s <- lexP
373          case s of
374            "LT" -> return LT
375            "EQ" -> return EQ
376            "GT" -> return GT
377            _    -> pfail
378     )
379
380   readListPrec = readListPrecDefault
381   readList     = readListDefault
382 \end{code}
383
384
385 %*********************************************************
386 %*                                                      *
387 \subsection{Structure instances of Read: Maybe, List etc}
388 %*                                                      *
389 %*********************************************************
390
391 For structured instances of Read we start using the precedences.  The
392 idea is then that 'parens (prec k p)' will fail immediately when trying
393 to parse it in a context with a higher precedence level than k. But if
394 there is one parenthesis parsed, then the required precedence level
395 drops to 0 again, and parsing inside p may succeed.
396
397 'appPrec' is just the precedence level of function application.  So,
398 if we are parsing function application, we'd better require the
399 precedence level to be at least 'appPrec'. Otherwise, we have to put
400 parentheses around it.
401
402 'step' is used to increase the precedence levels inside a
403 parser, and can be used to express left- or right- associativity. For
404 example, % is defined to be left associative, so we only increase
405 precedence on the right hand side.
406
407 Note how step is used in for example the Maybe parser to increase the
408 precedence beyond appPrec, so that basically only literals and
409 parenthesis-like objects such as (...) and [...] can be an argument to
410 'Just'.
411
412 \begin{code}
413 instance Read a => Read (Maybe a) where
414   readPrec =
415     parens
416     (do L.Ident "Nothing" <- lexP
417         return Nothing
418      +++
419      prec appPrec (
420         do L.Ident "Just" <- lexP
421            x              <- step readPrec
422            return (Just x))
423     )
424
425   readListPrec = readListPrecDefault
426   readList     = readListDefault
427
428 instance Read a => Read [a] where
429   readPrec     = readListPrec
430   readListPrec = readListPrecDefault
431   readList     = readListDefault
432
433 instance  (Ix a, Read a, Read b) => Read (Array a b)  where
434     readPrec = parens $ prec appPrec $
435                do L.Ident "array" <- lexP
436                   theBounds <- step readPrec
437                   vals   <- step readPrec
438                   return (array theBounds vals)
439
440     readListPrec = readListPrecDefault
441     readList     = readListDefault
442
443 instance Read L.Lexeme where
444   readPrec     = lexP
445   readListPrec = readListPrecDefault
446   readList     = readListDefault
447 \end{code}
448
449
450 %*********************************************************
451 %*                                                      *
452 \subsection{Numeric instances of Read}
453 %*                                                      *
454 %*********************************************************
455
456 \begin{code}
457 readNumber :: Num a => (L.Lexeme -> ReadPrec a) -> ReadPrec a
458 -- Read a signed number
459 readNumber convert =
460   parens
461   ( do x <- lexP
462        case x of
463          L.Symbol "-" -> do y <- lexP
464                             n <- convert y
465                             return (negate n)
466
467          _   -> convert x
468   )
469
470
471 convertInt :: Num a => L.Lexeme -> ReadPrec a
472 convertInt (L.Int i) = return (fromInteger i)
473 convertInt _         = pfail
474
475 convertFrac :: Fractional a => L.Lexeme -> ReadPrec a
476 convertFrac (L.Int i) = return (fromInteger i)
477 convertFrac (L.Rat r) = return (fromRational r)
478 convertFrac _         = pfail
479
480 instance Read Int where
481   readPrec     = readNumber convertInt
482   readListPrec = readListPrecDefault
483   readList     = readListDefault
484
485 instance Read Integer where
486   readPrec     = readNumber convertInt
487   readListPrec = readListPrecDefault
488   readList     = readListDefault
489
490 instance Read Float where
491   readPrec     = readNumber convertFrac
492   readListPrec = readListPrecDefault
493   readList     = readListDefault
494
495 instance Read Double where
496   readPrec     = readNumber convertFrac
497   readListPrec = readListPrecDefault
498   readList     = readListDefault
499
500 instance (Integral a, Read a) => Read (Ratio a) where
501   readPrec =
502     parens
503     ( prec ratioPrec
504       ( do x            <- step readPrec
505            L.Symbol "%" <- lexP
506            y            <- step readPrec
507            return (x % y)
508       )
509     )
510
511   readListPrec = readListPrecDefault
512   readList     = readListDefault
513 \end{code}
514
515
516 %*********************************************************
517 %*                                                      *
518         Tuple instances of Read, up to size 15
519 %*                                                      *
520 %*********************************************************
521
522 \begin{code}
523 instance Read () where
524   readPrec =
525     parens
526     ( paren
527       ( return ()
528       )
529     )
530
531   readListPrec = readListPrecDefault
532   readList     = readListDefault
533
534 instance (Read a, Read b) => Read (a,b) where
535   readPrec = wrap_tup read_tup2
536   readListPrec = readListPrecDefault
537   readList     = readListDefault
538
539 wrap_tup :: ReadPrec a -> ReadPrec a
540 wrap_tup p = parens (paren p)
541
542 read_comma :: ReadPrec ()
543 read_comma = do { L.Punc "," <- lexP; return () }
544
545 read_tup2 :: (Read a, Read b) => ReadPrec (a,b)
546 -- Reads "a , b"  no parens!
547 read_tup2 = do x <- readPrec
548                read_comma
549                y <- readPrec
550                return (x,y)
551
552 read_tup4 :: (Read a, Read b, Read c, Read d) => ReadPrec (a,b,c,d)
553 read_tup4 = do  (a,b) <- read_tup2
554                 read_comma
555                 (c,d) <- read_tup2
556                 return (a,b,c,d)
557
558
559 read_tup8 :: (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h)
560           => ReadPrec (a,b,c,d,e,f,g,h)
561 read_tup8 = do  (a,b,c,d) <- read_tup4
562                 read_comma
563                 (e,f,g,h) <- read_tup4
564                 return (a,b,c,d,e,f,g,h)
565
566
567 instance (Read a, Read b, Read c) => Read (a, b, c) where
568   readPrec = wrap_tup (do { (a,b) <- read_tup2; read_comma 
569                           ; c <- readPrec 
570                           ; return (a,b,c) })
571   readListPrec = readListPrecDefault
572   readList     = readListDefault
573
574 instance (Read a, Read b, Read c, Read d) => Read (a, b, c, d) where
575   readPrec = wrap_tup read_tup4
576   readListPrec = readListPrecDefault
577   readList     = readListDefault
578
579 instance (Read a, Read b, Read c, Read d, Read e) => Read (a, b, c, d, e) where
580   readPrec = wrap_tup (do { (a,b,c,d) <- read_tup4; read_comma
581                           ; e <- readPrec
582                           ; return (a,b,c,d,e) })
583   readListPrec = readListPrecDefault
584   readList     = readListDefault
585
586 instance (Read a, Read b, Read c, Read d, Read e, Read f)
587         => Read (a, b, c, d, e, f) where
588   readPrec = wrap_tup (do { (a,b,c,d) <- read_tup4; read_comma
589                           ; (e,f) <- read_tup2
590                           ; return (a,b,c,d,e,f) })
591   readListPrec = readListPrecDefault
592   readList     = readListDefault
593
594 instance (Read a, Read b, Read c, Read d, Read e, Read f, Read g)
595         => Read (a, b, c, d, e, f, g) where
596   readPrec = wrap_tup (do { (a,b,c,d) <- read_tup4; read_comma
597                           ; (e,f) <- read_tup2; read_comma
598                           ; g <- readPrec
599                           ; return (a,b,c,d,e,f,g) })
600   readListPrec = readListPrecDefault
601   readList     = readListDefault
602
603 instance (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h)
604         => Read (a, b, c, d, e, f, g, h) where
605   readPrec     = wrap_tup read_tup8
606   readListPrec = readListPrecDefault
607   readList     = readListDefault
608
609 instance (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
610           Read i)
611         => Read (a, b, c, d, e, f, g, h, i) where
612   readPrec = wrap_tup (do { (a,b,c,d,e,f,g,h) <- read_tup8; read_comma
613                           ; i <- readPrec
614                           ; return (a,b,c,d,e,f,g,h,i) })
615   readListPrec = readListPrecDefault
616   readList     = readListDefault
617
618 instance (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
619           Read i, Read j)
620         => Read (a, b, c, d, e, f, g, h, i, j) where
621   readPrec = wrap_tup (do { (a,b,c,d,e,f,g,h) <- read_tup8; read_comma
622                           ; (i,j) <- read_tup2
623                           ; return (a,b,c,d,e,f,g,h,i,j) })
624   readListPrec = readListPrecDefault
625   readList     = readListDefault
626
627 instance (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
628           Read i, Read j, Read k)
629         => Read (a, b, c, d, e, f, g, h, i, j, k) where
630   readPrec = wrap_tup (do { (a,b,c,d,e,f,g,h) <- read_tup8; read_comma
631                           ; (i,j) <- read_tup2; read_comma
632                           ; k <- readPrec
633                           ; return (a,b,c,d,e,f,g,h,i,j,k) })
634   readListPrec = readListPrecDefault
635   readList     = readListDefault
636
637 instance (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
638           Read i, Read j, Read k, Read l)
639         => Read (a, b, c, d, e, f, g, h, i, j, k, l) where
640   readPrec = wrap_tup (do { (a,b,c,d,e,f,g,h) <- read_tup8; read_comma
641                           ; (i,j,k,l) <- read_tup4
642                           ; return (a,b,c,d,e,f,g,h,i,j,k,l) })
643   readListPrec = readListPrecDefault
644   readList     = readListDefault
645
646 instance (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
647           Read i, Read j, Read k, Read l, Read m)
648         => Read (a, b, c, d, e, f, g, h, i, j, k, l, m) where
649   readPrec = wrap_tup (do { (a,b,c,d,e,f,g,h) <- read_tup8; read_comma
650                           ; (i,j,k,l) <- read_tup4; read_comma
651                           ; m <- readPrec
652                           ; return (a,b,c,d,e,f,g,h,i,j,k,l,m) })
653   readListPrec = readListPrecDefault
654   readList     = readListDefault
655
656 instance (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
657           Read i, Read j, Read k, Read l, Read m, Read n)
658         => Read (a, b, c, d, e, f, g, h, i, j, k, l, m, n) where
659   readPrec = wrap_tup (do { (a,b,c,d,e,f,g,h) <- read_tup8; read_comma
660                           ; (i,j,k,l) <- read_tup4; read_comma
661                           ; (m,n) <- read_tup2
662                           ; return (a,b,c,d,e,f,g,h,i,j,k,l,m,n) })
663   readListPrec = readListPrecDefault
664   readList     = readListDefault
665
666 instance (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
667           Read i, Read j, Read k, Read l, Read m, Read n, Read o)
668         => Read (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) where
669   readPrec = wrap_tup (do { (a,b,c,d,e,f,g,h) <- read_tup8; read_comma
670                           ; (i,j,k,l) <- read_tup4; read_comma
671                           ; (m,n) <- read_tup2; read_comma
672                           ; o <- readPrec
673                           ; return (a,b,c,d,e,f,g,h,i,j,k,l,m,n,o) })
674   readListPrec = readListPrecDefault
675   readList     = readListDefault
676 \end{code}
677
678 \begin{code}
679 -- XXX Can this be removed?
680
681 readp :: Read a => ReadP a
682 readp = readPrec_to_P readPrec minPrec
683 \end{code}
684
685 Instances for types of the generic deriving mechanism.
686
687 \begin{code}
688 deriving instance Read Arity
689 deriving instance Read Associativity
690 deriving instance Read Fixity
691 \end{code}