Use explicit language extensions & remove extension fields from base.cabal
[ghc-base.git] / Text / Read / Lex.hs
index cbfaaf8..222d6cf 100644 (file)
@@ -1,4 +1,5 @@
-{-# OPTIONS_GHC -fno-implicit-prelude #-}
+{-# LANGUAGE CPP, NoImplicitPrelude #-}
+
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  Text.Read.Lex
@@ -151,10 +152,10 @@ notANumber = 0 :% 0
 
 lexLitChar :: ReadP Lexeme
 lexLitChar =
-  do char '\''
+  do _ <- char '\''
      (c,esc) <- lexCharE
      guard (esc || c /= '\'')   -- Eliminate '' possibility
-     char '\''
+     _ <- char '\''
      return (Char c)
 
 lexChar :: ReadP Char
@@ -162,10 +163,10 @@ lexChar = do { (c,_) <- lexCharE; return c }
 
 lexCharE :: ReadP (Char, Bool)  -- "escaped or not"?
 lexCharE =
-  do c <- get
-     if c == '\\'
-       then do c <- lexEsc; return (c, True)
-       else do return (c, False)
+  do c1 <- get
+     if c1 == '\\'
+       then do c2 <- lexEsc; return (c2, True)
+       else do return (c1, False)
  where 
   lexEsc =
     lexEscChar
@@ -195,7 +196,7 @@ lexCharE =
        return (chr (fromInteger n))
 
   lexCntrlChar =
-    do char '^'
+    do _ <- char '^'
        c <- get
        case c of
          '@'  -> return '\^@'
@@ -279,7 +280,7 @@ lexCharE =
 
 lexString :: ReadP Lexeme
 lexString =
-  do char '"'
+  do _ <- char '"'
      body id
  where
   body f =
@@ -293,11 +294,11 @@ lexString =
                +++ lexCharE
   
   lexEmpty =
-    do char '\\'
+    do _ <- char '\\'
        c <- get
        case c of
          '&'           -> do return ()
-         _ | isSpace c -> do skipSpaces; char '\\'; return ()
+         _ | isSpace c -> do skipSpaces; _ <- char '\\'; return ()
          _             -> do pfail
 
 -- ---------------------------------------------------------------------------
@@ -314,7 +315,7 @@ lexNumber
                 
 lexHexOct :: ReadP Lexeme
 lexHexOct
-  = do  char '0'
+  = do  _ <- char '0'
         base <- lexBaseChar
         digits <- lexDigits base
         return (Int (val (fromIntegral base) 0 digits))
@@ -359,12 +360,12 @@ lexDecNumber =
 lexFrac :: ReadP (Maybe Digits)
 -- Read the fractional part; fail if it doesn't
 -- start ".d" where d is a digit
-lexFrac = do char '.'
-             frac <- lexDigits 10
-             return (Just frac)
+lexFrac = do _ <- char '.'
+             fraction <- lexDigits 10
+             return (Just fraction)
 
 lexExp :: ReadP (Maybe Integer)
-lexExp = do char 'e' +++ char 'E'
+lexExp = do _ <- char 'e' +++ char 'E'
             exp <- signedExp +++ lexInteger 10
             return (Just exp)
  where
@@ -382,7 +383,7 @@ lexDigits base =
      return xs
  where
   scan (c:cs) f = case valDig base c of
-                    Just n  -> do get; scan cs (f.(n:))
+                    Just n  -> do _ <- get; scan cs (f.(n:))
                     Nothing -> do return (f [])
   scan []     f = do return (f [])
 
@@ -393,13 +394,13 @@ lexInteger base =
 
 val :: Num a => a -> a -> Digits -> a
 -- val base y [d1,..,dn] = y ++ [d1,..,dn], as it were
-val base y []     = y
+val _    y []     = y
 val base y (x:xs) = y' `seq` val base y' xs
  where
   y' = y * base + fromIntegral x
 
 frac :: Integral a => a -> a -> a -> Digits -> Ratio a
-frac base a b []     = a % b
+frac _    a b []     = a % b
 frac base a b (x:xs) = a' `seq` b' `seq` frac base a' b' xs
  where
   a' = a * base + fromIntegral x
@@ -418,6 +419,9 @@ valDig 16 c
   | 'A' <= c && c <= 'F' = Just (ord c - ord 'A' + 10)
   | otherwise            = Nothing
 
+valDig _ _ = error "valDig: Bad base"
+
+valDecDig :: Char -> Maybe Int
 valDecDig c
   | '0' <= c && c <= '9' = Just (ord c - ord '0')
   | otherwise            = Nothing