f5a6c0db5f263b4b6d6b227f25272fbcc07fb259
[ghc-base.git] / GHC / Read.lhs
1 \begin{code}
2 {-# OPTIONS_GHC -fno-implicit-prelude #-}
3 -----------------------------------------------------------------------------
4 -- |
5 -- Module      :  GHC.Read
6 -- Copyright   :  (c) The University of Glasgow, 1994-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 'Read' class and instances for basic data types.
14 --
15 -----------------------------------------------------------------------------
16
17 -- #hide
18 module GHC.Read 
19   ( Read(..)   -- class
20   
21   -- ReadS type
22   , ReadS      -- :: *; = String -> [(a,String)]
23   
24   -- utility functions
25   , reads      -- :: Read a => ReadS a
26   , readp      -- :: Read a => ReadP a
27   , readEither -- :: Read a => String -> Either String a
28   , read       -- :: Read a => String -> a
29
30   -- H98 compatibility
31   , lex         -- :: ReadS String
32   , lexLitChar  -- :: ReadS String
33   , readLitChar -- :: ReadS Char
34   , lexDigits   -- :: ReadS String
35   
36   -- defining readers
37   , lexP       -- :: ReadPrec Lexeme
38   , paren      -- :: ReadPrec a -> ReadPrec a
39   , parens     -- :: ReadPrec a -> ReadPrec a
40   , list       -- :: ReadPrec a -> ReadPrec [a]
41   , choose     -- :: [(String, ReadPrec a)] -> ReadPrec a
42   , readListDefault, readListPrecDefault
43
44   -- Temporary
45   , readParen
46   )
47  where
48
49 import qualified Text.ParserCombinators.ReadP as P
50
51 import Text.ParserCombinators.ReadP
52   ( ReadP
53   , ReadS
54   , readP_to_S
55   )
56
57 import qualified Text.Read.Lex as L
58 -- Lex exports 'lex', which is also defined here,
59 -- hence the qualified import.
60 -- We can't import *anything* unqualified, because that
61 -- confuses Haddock.
62
63 import Text.ParserCombinators.ReadPrec
64
65 import Data.Maybe
66 import Data.Either
67
68 #ifndef __HADDOCK__
69 import {-# SOURCE #-} GHC.Unicode       ( isDigit )
70 #endif
71 import GHC.Num
72 import GHC.Real
73 import GHC.Float
74 import GHC.Show
75 import GHC.Base
76 import GHC.Arr
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 -- utility functions
228
229 -- | equivalent to 'readsPrec' with a precedence of 0.
230 reads :: Read a => ReadS a
231 reads = readsPrec minPrec
232
233 readp :: Read a => ReadP a
234 readp = readPrec_to_P readPrec minPrec
235
236 readEither :: Read a => String -> Either String a
237 readEither s =
238   case [ x | (x,"") <- readPrec_to_S read' minPrec s ] of
239     [x] -> Right x
240     []  -> Left "Prelude.read: no parse"
241     _   -> Left "Prelude.read: ambiguous parse"
242  where
243   read' =
244     do x <- readPrec
245        lift P.skipSpaces
246        return x
247
248 -- | The 'read' function reads input from a string, which must be
249 -- completely consumed by the input process.
250 read :: Read a => String -> a
251 read s = either error id (readEither s)
252
253 ------------------------------------------------------------------------
254 -- H98 compatibility
255
256 -- | The 'lex' function reads a single lexeme from the input, discarding
257 -- initial white space, and returning the characters that constitute the
258 -- lexeme.  If the input string contains only white space, 'lex' returns a
259 -- single successful \`lexeme\' consisting of the empty string.  (Thus
260 -- @'lex' \"\" = [(\"\",\"\")]@.)  If there is no legal lexeme at the
261 -- beginning of the input string, 'lex' fails (i.e. returns @[]@).
262 --
263 -- This lexer is not completely faithful to the Haskell lexical syntax
264 -- in the following respects:
265 --
266 -- * Qualified names are not handled properly
267 --
268 -- * Octal and hexadecimal numerics are not recognized as a single token
269 --
270 -- * Comments are not treated properly
271 lex :: ReadS String             -- As defined by H98
272 lex s  = readP_to_S L.hsLex s
273
274 -- | Read a string representation of a character, using Haskell
275 -- source-language escape conventions.  For example:
276 --
277 -- > lexLitChar  "\\nHello"  =  [("\\n", "Hello")]
278 --
279 lexLitChar :: ReadS String      -- As defined by H98
280 lexLitChar = readP_to_S (do { (s, _) <- P.gather L.lexChar ;
281                               return s })
282         -- There was a skipSpaces before the P.gather L.lexChar,
283         -- but that seems inconsistent with readLitChar
284
285 -- | Read a string representation of a character, using Haskell
286 -- source-language escape conventions, and convert it to the character
287 -- that it encodes.  For example:
288 --
289 -- > readLitChar "\\nHello"  =  [('\n', "Hello")]
290 --
291 readLitChar :: ReadS Char       -- As defined by H98
292 readLitChar = readP_to_S L.lexChar
293
294 -- | Reads a non-empty string of decimal digits.
295 lexDigits :: ReadS String
296 lexDigits = readP_to_S (P.munch1 isDigit)
297
298 ------------------------------------------------------------------------
299 -- utility parsers
300
301 lexP :: ReadPrec L.Lexeme
302 -- ^ Parse a single lexeme
303 lexP = lift L.lex
304
305 paren :: ReadPrec a -> ReadPrec a
306 -- ^ @(paren p)@ parses \"(P0)\"
307 --      where @p@ parses \"P0\" in precedence context zero
308 paren p = do L.Punc "(" <- lexP
309              x          <- reset p
310              L.Punc ")" <- lexP
311              return x
312
313 parens :: ReadPrec a -> ReadPrec a
314 -- ^ @(parens p)@ parses \"P\", \"(P0)\", \"((P0))\", etc, 
315 --      where @p@ parses \"P\"  in the current precedence context
316 --          and parses \"P0\" in precedence context zero
317 parens p = optional
318  where
319   optional  = p +++ mandatory
320   mandatory = paren optional
321
322 list :: ReadPrec a -> ReadPrec [a]
323 -- ^ @(list p)@ parses a list of things parsed by @p@,
324 -- using the usual square-bracket syntax.
325 list readx =
326   parens
327   ( do L.Punc "[" <- lexP
328        (listRest False +++ listNext)
329   )
330  where
331   listRest started =
332     do L.Punc c <- lexP
333        case c of
334          "]"           -> return []
335          "," | started -> listNext
336          _             -> pfail
337   
338   listNext =
339     do x  <- reset readx
340        xs <- listRest True
341        return (x:xs)
342
343 choose :: [(String, ReadPrec a)] -> ReadPrec a
344 -- ^ Parse the specified lexeme and continue as specified.
345 -- Esp useful for nullary constructors; e.g.
346 --    @choose [(\"A\", return A), (\"B\", return B)]@
347 choose sps = foldr ((+++) . try_one) pfail sps
348            where
349              try_one (s,p) = do { L.Ident s' <- lexP ;
350                                   if s == s' then p else pfail }
351 \end{code}
352
353
354 %*********************************************************
355 %*                                                      *
356 \subsection{Simple instances of Read}
357 %*                                                      *
358 %*********************************************************
359
360 \begin{code}
361 instance Read Char where
362   readPrec =
363     parens
364     ( do L.Char c <- lexP
365          return c
366     )
367
368   readListPrec =
369     parens
370     ( do L.String s <- lexP     -- Looks for "foo"
371          return s
372      +++
373       readListPrecDefault       -- Looks for ['f','o','o']
374     )                           -- (more generous than H98 spec)
375
376   readList = readListDefault
377
378 instance Read Bool where
379   readPrec =
380     parens
381     ( do L.Ident s <- lexP
382          case s of
383            "True"  -> return True
384            "False" -> return False
385            _       -> pfail
386     )
387
388   readListPrec = readListPrecDefault
389   readList     = readListDefault
390
391 instance Read Ordering where
392   readPrec =
393     parens
394     ( do L.Ident s <- lexP
395          case s of
396            "LT" -> return LT
397            "EQ" -> return EQ
398            "GT" -> return GT
399            _    -> pfail
400     )
401
402   readListPrec = readListPrecDefault
403   readList     = readListDefault
404 \end{code}
405
406
407 %*********************************************************
408 %*                                                      *
409 \subsection{Structure instances of Read: Maybe, List etc}
410 %*                                                      *
411 %*********************************************************
412
413 For structured instances of Read we start using the precedences.  The
414 idea is then that 'parens (prec k p)' will fail immediately when trying
415 to parse it in a context with a higher precedence level than k. But if
416 there is one parenthesis parsed, then the required precedence level
417 drops to 0 again, and parsing inside p may succeed.
418
419 'appPrec' is just the precedence level of function application.  So,
420 if we are parsing function application, we'd better require the
421 precedence level to be at least 'appPrec'. Otherwise, we have to put
422 parentheses around it.
423
424 'step' is used to increase the precedence levels inside a
425 parser, and can be used to express left- or right- associativity. For
426 example, % is defined to be left associative, so we only increase
427 precedence on the right hand side.
428
429 Note how step is used in for example the Maybe parser to increase the
430 precedence beyond appPrec, so that basically only literals and
431 parenthesis-like objects such as (...) and [...] can be an argument to
432 'Just'.
433
434 \begin{code}
435 instance Read a => Read (Maybe a) where
436   readPrec =
437     parens
438     (do L.Ident "Nothing" <- lexP
439         return Nothing
440      +++
441      prec appPrec (
442         do L.Ident "Just" <- lexP
443            x              <- step readPrec
444            return (Just x))
445     )
446
447   readListPrec = readListPrecDefault
448   readList     = readListDefault
449
450 instance (Read a, Read b) => Read (Either a b) where
451   readPrec =
452     parens
453     ( prec appPrec
454       ( do L.Ident "Left" <- lexP
455            x            <- step readPrec
456            return (Left x)
457        +++
458         do L.Ident "Right" <- lexP
459            y             <- step readPrec
460            return (Right y)
461       )
462     )
463
464   readListPrec = readListPrecDefault
465   readList     = readListDefault
466
467 instance Read a => Read [a] where
468   readPrec     = readListPrec
469   readListPrec = readListPrecDefault
470   readList     = readListDefault
471
472 instance  (Ix a, Read a, Read b) => Read (Array a b)  where
473     readPrec = parens $ prec appPrec $
474                do L.Ident "array" <- lexP
475                   bounds <- step readPrec
476                   vals   <- step readPrec
477                   return (array bounds vals)
478
479     readListPrec = readListPrecDefault
480     readList     = readListDefault
481
482 instance Read L.Lexeme where
483   readPrec     = lexP
484   readListPrec = readListPrecDefault
485   readList     = readListDefault
486 \end{code}
487
488
489 %*********************************************************
490 %*                                                      *
491 \subsection{Numeric instances of Read}
492 %*                                                      *
493 %*********************************************************
494
495 \begin{code}
496 readNumber :: Num a => (L.Lexeme -> Maybe a) -> ReadPrec a
497 -- Read a signed number
498 readNumber convert =
499   parens
500   ( do x <- lexP
501        case x of
502          L.Symbol "-" -> do n <- readNumber convert
503                             return (negate n)
504        
505          _   -> case convert x of
506                    Just n  -> return n
507                    Nothing -> pfail
508   )
509
510 convertInt :: Num a => L.Lexeme -> Maybe a
511 convertInt (L.Int i) = Just (fromInteger i)
512 convertInt _         = Nothing
513
514 convertFrac :: Fractional a => L.Lexeme -> Maybe a
515 convertFrac (L.Int i) = Just (fromInteger i)
516 convertFrac (L.Rat r) = Just (fromRational r)
517 convertFrac _         = Nothing
518
519 instance Read Int where
520   readPrec     = readNumber convertInt
521   readListPrec = readListPrecDefault
522   readList     = readListDefault
523
524 instance Read Integer where
525   readPrec     = readNumber convertInt
526   readListPrec = readListPrecDefault
527   readList     = readListDefault
528
529 instance Read Float where
530   readPrec     = readNumber convertFrac
531   readListPrec = readListPrecDefault
532   readList     = readListDefault
533
534 instance Read Double where
535   readPrec     = readNumber convertFrac
536   readListPrec = readListPrecDefault
537   readList     = readListDefault
538
539 instance (Integral a, Read a) => Read (Ratio a) where
540   readPrec =
541     parens
542     ( prec ratioPrec
543       ( do x            <- step readPrec
544            L.Symbol "%" <- lexP
545            y            <- step readPrec
546            return (x % y)
547       )
548     )
549
550   readListPrec = readListPrecDefault
551   readList     = readListDefault
552 \end{code}
553
554
555 %*********************************************************
556 %*                                                      *
557         Tuple instances of Read, up to size 15
558 %*                                                      *
559 %*********************************************************
560
561 \begin{code}
562 instance Read () where
563   readPrec =
564     parens
565     ( paren
566       ( return ()
567       )
568     )
569
570   readListPrec = readListPrecDefault
571   readList     = readListDefault
572
573 instance (Read a, Read b) => Read (a,b) where
574   readPrec = wrap_tup read_tup2
575   readListPrec = readListPrecDefault
576   readList     = readListDefault
577
578 wrap_tup :: ReadPrec a -> ReadPrec a
579 wrap_tup p = parens (paren p)
580
581 read_comma :: ReadPrec ()
582 read_comma = do { L.Punc "," <- lexP; return () }
583
584 read_tup2 :: (Read a, Read b) => ReadPrec (a,b)
585 -- Reads "a , b"  no parens!
586 read_tup2 = do x <- readPrec
587                read_comma
588                y <- readPrec
589                return (x,y)
590
591 read_tup4 :: (Read a, Read b, Read c, Read d) => ReadPrec (a,b,c,d)
592 read_tup4 = do  (a,b) <- read_tup2
593                 read_comma
594                 (c,d) <- read_tup2
595                 return (a,b,c,d)
596
597
598 read_tup8 :: (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h)
599           => ReadPrec (a,b,c,d,e,f,g,h)
600 read_tup8 = do  (a,b,c,d) <- read_tup4
601                 read_comma
602                 (e,f,g,h) <- read_tup4
603                 return (a,b,c,d,e,f,g,h)
604
605
606 instance (Read a, Read b, Read c) => Read (a, b, c) where
607   readPrec = wrap_tup (do { (a,b) <- read_tup2; read_comma 
608                           ; c <- readPrec 
609                           ; return (a,b,c) })
610   readListPrec = readListPrecDefault
611   readList     = readListDefault
612
613 instance (Read a, Read b, Read c, Read d) => Read (a, b, c, d) where
614   readPrec = wrap_tup read_tup4
615   readListPrec = readListPrecDefault
616   readList     = readListDefault
617
618 instance (Read a, Read b, Read c, Read d, Read e) => Read (a, b, c, d, e) where
619   readPrec = wrap_tup (do { (a,b,c,d) <- read_tup4; read_comma
620                           ; e <- readPrec
621                           ; return (a,b,c,d,e) })
622   readListPrec = readListPrecDefault
623   readList     = readListDefault
624
625 instance (Read a, Read b, Read c, Read d, Read e, Read f)
626         => Read (a, b, c, d, e, f) where
627   readPrec = wrap_tup (do { (a,b,c,d) <- read_tup4; read_comma
628                           ; (e,f) <- read_tup2
629                           ; return (a,b,c,d,e,f) })
630   readListPrec = readListPrecDefault
631   readList     = readListDefault
632
633 instance (Read a, Read b, Read c, Read d, Read e, Read f, Read g)
634         => Read (a, b, c, d, e, f, g) where
635   readPrec = wrap_tup (do { (a,b,c,d) <- read_tup4; read_comma
636                           ; (e,f) <- read_tup2; read_comma
637                           ; g <- readPrec
638                           ; return (a,b,c,d,e,f,g) })
639   readListPrec = readListPrecDefault
640   readList     = readListDefault
641
642 instance (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h)
643         => Read (a, b, c, d, e, f, g, h) where
644   readPrec     = wrap_tup read_tup8
645   readListPrec = readListPrecDefault
646   readList     = readListDefault
647
648 instance (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
649           Read i)
650         => Read (a, b, c, d, e, f, g, h, i) where
651   readPrec = wrap_tup (do { (a,b,c,d,e,f,g,h) <- read_tup8; read_comma
652                           ; i <- readPrec
653                           ; return (a,b,c,d,e,f,g,h,i) })
654   readListPrec = readListPrecDefault
655   readList     = readListDefault
656
657 instance (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
658           Read i, Read j)
659         => Read (a, b, c, d, e, f, g, h, i, j) where
660   readPrec = wrap_tup (do { (a,b,c,d,e,f,g,h) <- read_tup8; read_comma
661                           ; (i,j) <- read_tup2
662                           ; return (a,b,c,d,e,f,g,h,i,j) })
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)
668         => Read (a, b, c, d, e, f, g, h, i, j, k) where
669   readPrec = wrap_tup (do { (a,b,c,d,e,f,g,h) <- read_tup8; read_comma
670                           ; (i,j) <- read_tup2; read_comma
671                           ; k <- readPrec
672                           ; return (a,b,c,d,e,f,g,h,i,j,k) })
673   readListPrec = readListPrecDefault
674   readList     = readListDefault
675
676 instance (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
677           Read i, Read j, Read k, Read l)
678         => Read (a, b, c, d, e, f, g, h, i, j, k, l) where
679   readPrec = wrap_tup (do { (a,b,c,d,e,f,g,h) <- read_tup8; read_comma
680                           ; (i,j,k,l) <- read_tup4
681                           ; return (a,b,c,d,e,f,g,h,i,j,k,l) })
682   readListPrec = readListPrecDefault
683   readList     = readListDefault
684
685 instance (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
686           Read i, Read j, Read k, Read l, Read m)
687         => Read (a, b, c, d, e, f, g, h, i, j, k, l, m) where
688   readPrec = wrap_tup (do { (a,b,c,d,e,f,g,h) <- read_tup8; read_comma
689                           ; (i,j,k,l) <- read_tup4; read_comma
690                           ; m <- readPrec
691                           ; return (a,b,c,d,e,f,g,h,i,j,k,l,m) })
692   readListPrec = readListPrecDefault
693   readList     = readListDefault
694
695 instance (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
696           Read i, Read j, Read k, Read l, Read m, Read n)
697         => Read (a, b, c, d, e, f, g, h, i, j, k, l, m, n) where
698   readPrec = wrap_tup (do { (a,b,c,d,e,f,g,h) <- read_tup8; read_comma
699                           ; (i,j,k,l) <- read_tup4; read_comma
700                           ; (m,n) <- read_tup2
701                           ; return (a,b,c,d,e,f,g,h,i,j,k,l,m,n) })
702   readListPrec = readListPrecDefault
703   readList     = readListDefault
704
705 instance (Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h,
706           Read i, Read j, Read k, Read l, Read m, Read n, Read o)
707         => Read (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) where
708   readPrec = wrap_tup (do { (a,b,c,d,e,f,g,h) <- read_tup8; read_comma
709                           ; (i,j,k,l) <- read_tup4; read_comma
710                           ; (m,n) <- read_tup2; read_comma
711                           ; o <- readPrec
712                           ; return (a,b,c,d,e,f,g,h,i,j,k,l,m,n,o) })
713   readListPrec = readListPrecDefault
714   readList     = readListDefault
715 \end{code}