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