[project @ 2000-04-10 12:12:27 by simonpj]
[ghc-hetmet.git] / ghc / lib / std / PrelRead.lhs
index a03963b..3f64865 100644 (file)
@@ -11,18 +11,19 @@ Instances of the Read class.
 
 module PrelRead where
 
-import {-# SOURCE #-} PrelErr ( error )
+import PrelErr         ( error )
+import PrelEnum                ( Enum(..) )
 import PrelNum
-import PrelNumExtra
+import PrelReal
+import PrelFloat
 import PrelList
 import PrelTup
 import PrelMaybe
-import PrelEither
+import PrelShow                -- isAlpha etc
 import PrelBase
-import Monad
 
--- needed for readIO.
-import PrelIOBase ( IO, userError )
+-- needed for readIO and instance Read Buffermode
+import PrelIOBase ( IO, userError, BufferMode(..) )
 import PrelException ( ioError )
 \end{code}
 
@@ -57,6 +58,22 @@ class  Read a  where
     readList   = readList__ reads
 \end{code}
 
+In this module we treat [(a,String)] as a monad in MonadPlus
+But MonadPlus isn't defined yet, so we simply give local
+declarations for mzero and guard suitable for this particular
+type.  It would also be reasonably to move MonadPlus to PrelBase
+along with Monad and Functor, but that seems overkill for one 
+example
+
+\begin{code}
+mzero :: [a]
+mzero = []
+
+guard :: Bool -> [()]
+guard True  = [()]
+guard False = []
+\end{code}
+
 %*********************************************************
 %*                                                     *
 \subsection{Utility functions}
@@ -173,6 +190,8 @@ lex (c:s) | isSingle c = return ([c],s)
                (nam,t) <- return (span isIdChar s)
                return (c:nam, t)
           | isDigit c  = do
+{- Removed, 13/03/2000 by SDM.
+   Doesn't work, and not required by Haskell report.
                 let
                  (pred, s', isDec) =
                    case s of
@@ -181,9 +200,9 @@ lex (c:s) | isSingle c = return ([c],s)
                      ('x':rs) -> (isHexDigit, rs, False)
                      ('X':rs) -> (isHexDigit, rs, False)
                      _        -> (isDigit, s, True)
-
-                (ds,s)  <- return (span pred s')
-                (fe,t)  <- lexFracExp isDec s
+-}
+                (ds,s)  <- return (span isDigit s)
+                (fe,t)  <- lexFracExp s
                 return (c:ds++fe,t)
           | otherwise  = mzero    -- bad character
              where
@@ -191,11 +210,11 @@ lex (c:s) | isSingle c = return ([c],s)
               isSym c    =  c `elem` "!@#$%&*+./<=>?\\^|:-~"
               isIdChar c =  isAlphaNum c || c `elem` "_'"
 
-              lexFracExp True ('.':cs)   = do
+              lexFracExp ('.':c:cs) | isDigit c = do
                        (ds,t) <- lex0Digits cs
                        (e,u)  <- lexExp t
-                       return ('.':ds++e,u)
-              lexFracExp _ s        = return ("",s)
+                       return ('.':c:ds++e,u)
+              lexFracExp s        = return ("",s)
 
               lexExp (e:s) | e `elem` "eE" = 
                  (do
@@ -603,3 +622,26 @@ readRational__ top_s
 #endif
 
 \end{code}
+
+%*********************************************************
+%*                                                     *
+\subsection{Reading BufferMode}
+%*                                                     *
+%*********************************************************
+
+This instance decl is here rather than somewhere more appropriate in
+order that we can avoid both orphan-instance modules and recursive
+dependencies.
+
+\begin{code}
+instance Read BufferMode where
+    readsPrec _ = 
+      readParen False
+       (\r ->  let lr = lex r
+               in
+               [(NoBuffering, rest)       | ("NoBuffering", rest) <- lr] ++
+               [(LineBuffering,rest)      | ("LineBuffering",rest) <- lr] ++
+               [(BlockBuffering mb,rest2) | ("BlockBuffering",rest1) <- lr,
+                                            (mb, rest2) <- reads rest1])
+
+\end{code}