[project @ 1998-12-02 13:17:09 by simonm]
[ghc-hetmet.git] / ghc / lib / std / PrelRead.lhs
1 %
2 % (c) The AQUA Project, Glasgow University, 1994-1998
3 %
4
5 \section[PrelRead]{Module @PrelRead@}
6
7 Instances of the Read class.
8
9 \begin{code}
10 {-# OPTIONS -fno-implicit-prelude #-}
11
12 module PrelRead where
13
14 import {-# SOURCE #-} PrelErr ( error )
15 import PrelNum
16 import PrelNumExtra
17 import PrelList
18 import PrelTup
19 import PrelMaybe
20 import PrelEither
21 import PrelBase
22 import Monad
23
24 -- needed for readIO.
25 import PrelIOBase ( IO, userError )
26 import PrelException ( fail )
27 \end{code}
28
29 %*********************************************************
30 %*                                                      *
31 \subsection{The @Read@ class}
32 %*                                                      *
33 %*********************************************************
34
35 Note: if you compile this with -DNEW_READS_REP, you'll get
36 a (simpler) ReadS representation that only allow one valid
37 parse of a string of characters, instead of a list of
38 possible ones.
39
40 [changing the ReadS rep has implications for the deriving
41 machinery for Read, a change that hasn't been made, so you
42 probably won't want to compile in this new rep. except
43 when in an experimental mood.]
44
45 \begin{code}
46
47 #ifndef NEW_READS_REP
48 type  ReadS a   = String -> [(a,String)]
49 #else
50 type  ReadS a   = String -> Maybe (a,String)
51 #endif
52
53 class  Read a  where
54     readsPrec :: Int -> ReadS a
55
56     readList  :: ReadS [a]
57     readList   = readList__ reads
58 \end{code}
59
60 %*********************************************************
61 %*                                                      *
62 \subsection{Utility functions}
63 %*                                                      *
64 %*********************************************************
65
66 \begin{code}
67 reads           :: (Read a) => ReadS a
68 reads           =  readsPrec 0
69
70 read            :: (Read a) => String -> a
71 read s          =  
72    case read_s s of
73 #ifndef NEW_READS_REP
74       [x]     -> x
75       []      -> error "PreludeText.read: no parse"
76       _       -> error "PreludeText.read: ambiguous parse"
77 #else
78       Just x  -> x
79       Nothing -> error "PreludeText.read: no parse"
80 #endif
81  where
82   read_s s = do
83     (x,t)   <- reads s
84     ("","") <- lex t
85     return x
86
87   -- raises an exception instead of an error
88 readIO          :: Read a => String -> IO a
89 readIO s        =  case (do { (x,t) <- reads s ; ("","") <- lex t ; return x }) of
90 #ifndef NEW_READS_REP
91                         [x]    -> return x
92                         []     -> fail (userError "PreludeIO.readIO: no parse")
93                         _      -> fail (userError "PreludeIO.readIO: ambiguous parse")
94 #else
95                         Just x -> return x
96                         Nothing  -> fail (userError "PreludeIO.readIO: no parse")
97 #endif
98
99 \end{code}
100
101 \begin{code}
102 readParen       :: Bool -> ReadS a -> ReadS a
103 readParen b g   =  if b then mandatory else optional
104                    where optional r  = g r ++ mandatory r
105                          mandatory r = do
106                                 ("(",s) <- lex r
107                                 (x,t)   <- optional s
108                                 (")",u) <- lex t
109                                 return (x,u)
110
111
112 readList__ :: ReadS a -> ReadS [a]
113
114 readList__ readx
115   = readParen False (\r -> do
116                        ("[",s) <- lex r
117                        readl s)
118   where readl  s = 
119            (do { ("]",t) <- lex s ; return ([],t) }) ++
120            (do { (x,t) <- readx s ; (xs,u) <- readl2 t ; return (x:xs,u) })
121
122         readl2 s = 
123            (do { ("]",t) <- lex s ; return ([],t) }) ++
124            (do { (",",t) <- lex s ; (x,u) <- readx t ; (xs,v) <- readl2 u ; return (x:xs,v) })
125
126 \end{code}
127
128
129 %*********************************************************
130 %*                                                      *
131 \subsection{Lexical analysis}
132 %*                                                      *
133 %*********************************************************
134
135 This lexer is not completely faithful to the Haskell lexical syntax.
136 Current limitations:
137    Qualified names are not handled properly
138    A `--' does not terminate a symbol
139    Octal and hexidecimal numerics are not recognized as a single token
140
141 \begin{code}
142 lex                   :: ReadS String
143
144 lex ""                = return ("","")
145 lex (c:s) | isSpace c = lex (dropWhile isSpace s)
146 lex ('\'':s)          = do
147             (ch, '\'':t) <- lexLitChar s
148             guard (ch /= "'")
149             return ('\'':ch++"'", t)
150 lex ('"':s)           = do
151             (str,t) <- lexString s
152             return ('"':str, t)
153
154           where
155             lexString ('"':s) = return ("\"",s)
156             lexString s = do
157                     (ch,t)  <- lexStrItem s
158                     (str,u) <- lexString t
159                     return (ch++str, u)
160
161             
162             lexStrItem ('\\':'&':s) = return ("\\&",s)
163             lexStrItem ('\\':c:s) | isSpace c = do
164                         ('\\':t) <- return (dropWhile isSpace s)
165                         return ("\\&",t)
166             lexStrItem s            = lexLitChar s
167      
168 lex (c:s) | isSingle c = return ([c],s)
169           | isSym c    = do
170                 (sym,t) <- return (span isSym s)
171                 return (c:sym,t)
172           | isAlpha c  = do
173                 (nam,t) <- return (span isIdChar s)
174                 return (c:nam, t)
175           | isDigit c  = do
176                  (ds,s)  <- return (span isDigit s)
177                  (fe,t)  <- lexFracExp s
178                  return (c:ds++fe,t)
179           | otherwise  = zero    -- bad character
180              where
181               isSingle c =  c `elem` ",;()[]{}_`"
182               isSym c    =  c `elem` "!@#$%&*+./<=>?\\^|:-~"
183               isIdChar c =  isAlphanum c || c `elem` "_'"
184
185               lexFracExp ('.':cs)   = do
186                         (ds,t) <- lex0Digits cs
187                         (e,u)  <- lexExp t
188                         return ('.':ds++e,u)
189               lexFracExp s          = return ("",s)
190
191               lexExp (e:s) | e `elem` "eE" = 
192                   (do
193                     (c:t) <- return s
194                     guard (c `elem` "+-")
195                     (ds,u) <- lexDigits t
196                     return (e:c:ds,u))      ++
197                   (do
198                     (ds,t) <- lexDigits s
199                     return (e:ds,t))
200
201               lexExp s = return ("",s)
202
203 lexDigits               :: ReadS String 
204 lexDigits               =  nonnull isDigit
205
206 -- 0 or more digits
207 lex0Digits               :: ReadS String 
208 lex0Digits  s            =  return (span isDigit s)
209
210 nonnull                 :: (Char -> Bool) -> ReadS String
211 nonnull p s             = do
212             (cs@(_:_),t) <- return (span p s)
213             return (cs,t)
214
215 lexLitChar              :: ReadS String
216 lexLitChar ('\\':s)     =  do
217             (esc,t) <- lexEsc s
218             return ('\\':esc, t)
219         where
220         lexEsc (c:s)     | c `elem` "abfnrtv\\\"'" = return ([c],s)
221         lexEsc s@(d:_)   | isDigit d               = lexDigits s
222         lexEsc _                                   = zero
223
224 lexLitChar (c:s)        =  return ([c],s)
225 lexLitChar ""           =  zero
226 \end{code}
227
228 %*********************************************************
229 %*                                                      *
230 \subsection{Instances of @Read@}
231 %*                                                      *
232 %*********************************************************
233
234 \begin{code}
235 instance  Read Char  where
236     readsPrec p      = readParen False
237                             (\r -> do
238                                 ('\'':s,t) <- lex r
239                                 (c,_)      <- readLitChar s
240                                 return (c,t))
241
242     readList = readParen False (\r -> do
243                                 ('"':s,t) <- lex r
244                                 (l,_)     <- readl s
245                                 return (l,t))
246                where readl ('"':s)      = return ("",s)
247                      readl ('\\':'&':s) = readl s
248                      readl s            = do
249                             (c,t)  <- readLitChar s 
250                             (cs,u) <- readl t
251                             return (c:cs,u)
252
253 instance Read Bool where
254     readsPrec p = readParen False
255                         (\r ->
256                            lex r >>= \ lr ->
257                            (do { ("True", rest)  <- return lr ; return (True,  rest) }) ++
258                            (do { ("False", rest) <- return lr ; return (False, rest) }))
259                 
260
261 instance Read Ordering where
262     readsPrec p = readParen False
263                         (\r -> 
264                            lex r >>= \ lr ->
265                            (do { ("LT", rest) <- return lr ; return (LT,  rest) }) ++
266                            (do { ("EQ", rest) <- return lr ; return (EQ, rest) })  ++
267                            (do { ("GT", rest) <- return lr ; return (GT, rest) }))
268
269 instance Read a => Read (Maybe a) where
270     readsPrec p = readParen False
271                         (\r -> 
272                             lex r >>= \ lr ->
273                             (do { ("Nothing", rest) <- return lr ; return (Nothing, rest)}) ++
274                             (do 
275                                 ("Just", rest1) <- return lr
276                                 (x, rest2)      <- reads rest1
277                                 return (Just x, rest2)))
278
279 instance (Read a, Read b) => Read (Either a b) where
280     readsPrec p = readParen False
281                         (\r ->
282                             lex r >>= \ lr ->
283                             (do 
284                                 ("Left", rest1) <- return lr
285                                 (x, rest2)      <- reads rest1
286                                 return (Left x, rest2)) ++
287                             (do 
288                                 ("Right", rest1) <- return lr
289                                 (x, rest2)      <- reads rest1
290                                 return (Right x, rest2)))
291
292 instance  Read Int  where
293     readsPrec p x = readSigned readDec x
294
295 instance  Read Integer  where
296     readsPrec p x = readSigned readDec x
297
298 instance  Read Float  where
299     readsPrec p x = readSigned readFloat x
300
301 instance  Read Double  where
302     readsPrec p x = readSigned readFloat x
303
304 instance  (Integral a, Read a)  => Read (Ratio a)  where
305     readsPrec p  =  readParen (p > ratio_prec)
306                               (\r -> do
307                                 (x,s)   <- reads r
308                                 ("%",t) <- lex s
309                                 (y,u)   <- reads t
310                                 return (x%y,u))
311
312 instance  (Read a) => Read [a]  where
313     readsPrec p         = readList
314
315 instance Read () where
316     readsPrec p    = readParen False
317                             (\r -> do
318                                 ("(",s) <- lex r
319                                 (")",t) <- lex s
320                                 return ((),t))
321
322 instance  (Read a, Read b) => Read (a,b)  where
323     readsPrec p = readParen False
324                             (\r -> do
325                                 ("(",s) <- lex r
326                                 (x,t)   <- readsPrec 0 s
327                                 (",",u) <- lex t
328                                 (y,v)   <- readsPrec 0 u
329                                 (")",w) <- lex v
330                                 return ((x,y), w))
331
332 instance (Read a, Read b, Read c) => Read (a, b, c) where
333     readsPrec p = readParen False
334                             (\a -> do
335                                 ("(",b) <- lex a
336                                 (x,c)   <- readsPrec 0 b
337                                 (",",d) <- lex c
338                                 (y,e)   <- readsPrec 0 d
339                                 (",",f) <- lex e
340                                 (z,g)   <- readsPrec 0 f
341                                 (")",h) <- lex g
342                                 return ((x,y,z), h))
343
344 instance (Read a, Read b, Read c, Read d) => Read (a, b, c, d) where
345     readsPrec p = readParen False
346                             (\a -> do
347                                 ("(",b) <- lex a
348                                 (w,c)   <- readsPrec 0 b
349                                 (",",d) <- lex c
350                                 (x,e)   <- readsPrec 0 d
351                                 (",",f) <- lex e
352                                 (y,g)   <- readsPrec 0 f
353                                 (",",h) <- lex g
354                                 (z,h)   <- readsPrec 0 h
355                                 (")",i) <- lex h
356                                 return ((w,x,y,z), i))
357
358 instance (Read a, Read b, Read c, Read d, Read e) => Read (a, b, c, d, e) where
359     readsPrec p = readParen False
360                             (\a -> do
361                                 ("(",b) <- lex a
362                                 (v,c)   <- readsPrec 0 b
363                                 (",",d) <- lex c
364                                 (w,e)   <- readsPrec 0 d
365                                 (",",f) <- lex e
366                                 (x,g)   <- readsPrec 0 f
367                                 (",",h) <- lex g
368                                 (y,i)   <- readsPrec 0 h
369                                 (",",j) <- lex i
370                                 (z,k)   <- readsPrec 0 j
371                                 (")",l) <- lex k
372                                 return ((v,w,x,y,z), l))
373 \end{code}
374
375
376 %*********************************************************
377 %*                                                      *
378 \subsection{Reading characters}
379 %*                                                      *
380 %*********************************************************
381
382 \begin{code}
383 readLitChar             :: ReadS Char
384
385 readLitChar ('\\':s)    =  readEsc s
386         where
387         readEsc ('a':s)  = return ('\a',s)
388         readEsc ('b':s)  = return ('\b',s)
389         readEsc ('f':s)  = return ('\f',s)
390         readEsc ('n':s)  = return ('\n',s)
391         readEsc ('r':s)  = return ('\r',s)
392         readEsc ('t':s)  = return ('\t',s)
393         readEsc ('v':s)  = return ('\v',s)
394         readEsc ('\\':s) = return ('\\',s)
395         readEsc ('"':s)  = return ('"',s)
396         readEsc ('\'':s) = return ('\'',s)
397         readEsc ('^':c:s) | c >= '@' && c <= '_'
398                          = return (chr (ord c - ord '@'), s)
399         readEsc s@(d:_) | isDigit d
400                          = do
401                           (n,t) <- readDec s
402                           return (chr n,t)
403         readEsc ('o':s)  = do
404                           (n,t) <- readOct s
405                           return (chr n,t)
406         readEsc ('x':s)  = do
407                           (n,t) <- readHex s
408                           return (chr n,t)
409
410         readEsc s@(c:_) | isUpper c
411                          = let table = ('\DEL', "DEL") : zip ['\NUL'..] asciiTab
412                            in case [(c,s') | (c, mne) <- table,
413                                              ([],s') <- [match mne s]]
414                               of (pr:_) -> return pr
415                                  []     -> zero
416         readEsc _        = zero
417
418 readLitChar (c:s)       =  return (c,s)
419
420 match                   :: (Eq a) => [a] -> [a] -> ([a],[a])
421 match (x:xs) (y:ys) | x == y  =  match xs ys
422 match xs     ys               =  (xs,ys)
423
424 \end{code}
425
426
427 %*********************************************************
428 %*                                                      *
429 \subsection{Reading numbers}
430 %*                                                      *
431 %*********************************************************
432
433 Note: reading numbers at bases different than 10, does not
434 include lexing common prefixes such as '0x' or '0o' etc.
435
436 \begin{code}
437 {-# SPECIALISE readDec :: 
438                 ReadS Int,
439                 ReadS Integer #-}
440 readDec :: (Integral a) => ReadS a
441 readDec = readInt 10 isDigit (\d -> ord d - ord_0)
442
443 {-# SPECIALISE readOct :: 
444                 ReadS Int,
445                 ReadS Integer #-}
446 readOct :: (Integral a) => ReadS a
447 readOct = readInt 8 isOctDigit (\d -> ord d - ord_0)
448
449 {-# SPECIALISE readHex :: 
450                 ReadS Int,
451                 ReadS Integer #-}
452 readHex :: (Integral a) => ReadS a
453 readHex = readInt 16 isHexDigit hex
454             where hex d = ord d - (if isDigit d then ord_0
455                                    else ord (if isUpper d then 'A' else 'a') - 10)
456
457 readInt :: (Integral a) => a -> (Char -> Bool) -> (Char -> Int) -> ReadS a
458 readInt radix isDig digToInt s = do
459     (ds,r) <- nonnull isDig s
460     return (foldl1 (\n d -> n * radix + d) (map (fromInt . digToInt) ds), r)
461
462 {-# SPECIALISE readSigned ::
463                 ReadS Int     -> ReadS Int,
464                 ReadS Integer -> ReadS Integer,
465                 ReadS Double  -> ReadS Double       #-}
466 readSigned :: (Real a) => ReadS a -> ReadS a
467 readSigned readPos = readParen False read'
468                      where read' r  = read'' r ++
469                                       (do
470                                         ("-",s) <- lex r
471                                         (x,t)   <- read'' s
472                                         return (-x,t))
473                            read'' r = do
474                                (str,s) <- lex r
475                                (n,"")  <- readPos str
476                                return (n,s)
477 \end{code}
478
479 The functions readFloat below uses rational arithmetic
480 to ensure correct conversion between the floating-point radix and
481 decimal.  It is often possible to use a higher-precision floating-
482 point type to obtain the same results.
483
484 \begin{code}
485 {-# SPECIALISE readFloat ::
486                     ReadS Double,
487                     ReadS Float     #-} 
488 readFloat :: (RealFloat a) => ReadS a
489 readFloat r = do
490     (x,t) <- readRational r
491     return (fromRational x,t)
492
493 readRational :: ReadS Rational -- NB: doesn't handle leading "-"
494
495 readRational r =
496    (do 
497       (n,d,s) <- readFix r
498       (k,t)   <- readExp s
499       return ((n%1)*10^^(k-d), t )) ++
500    (do
501       ("NaN",t) <- lex r
502       return (0/0,t) ) ++
503    (do
504       ("Infinity",t) <- lex r
505       return (1/0,t) )
506  where
507      readFix r = do
508         (ds,s)  <- lexDigits r
509         (ds',t) <- lexDotDigits s
510         return (read (ds++ds'), length ds', t)
511
512      readExp (e:s) | e `elem` "eE" = readExp' s
513      readExp s                     = return (0,s)
514
515      readExp' ('+':s) = readDec s
516      readExp' ('-':s) = do
517                         (k,t) <- readDec s
518                         return (-k,t)
519      readExp' s       = readDec s
520
521      lexDotDigits ('.':s) = lex0Digits s
522      lexDotDigits s       = return ("",s)
523
524 readRational__ :: String -> Rational -- we export this one (non-std)
525                                     -- NB: *does* handle a leading "-"
526 readRational__ top_s
527   = case top_s of
528       '-' : xs -> - (read_me xs)
529       xs       -> read_me xs
530   where
531     read_me s
532       = case (do { (x,t) <- readRational s ; ("","") <- lex t ; return x }) of
533 #ifndef NEW_READS_REP
534           [x] -> x
535           []  -> error ("readRational__: no parse:"        ++ top_s)
536           _   -> error ("readRational__: ambiguous parse:" ++ top_s)
537 #else
538           Just x  -> x
539           Nothing -> error ("readRational__: no parse:"        ++ top_s)
540 #endif
541
542 \end{code}