[project @ 2004-08-13 13:04:50 by simonmar]
[ghc-hetmet.git] / ghc / compiler / parser / Ctype.lhs
index adcaec2..d97d5e0 100644 (file)
@@ -9,13 +9,16 @@ module Ctype
        , is_lower      -- Char# -> Bool
        , is_upper      -- Char# -> Bool
        , is_digit      -- Char# -> Bool
+
+       , is_hexdigit, is_octdigit
+       , hexDigit, octDecDigit
        ) where
-\end{code}
 
-\begin{code}
-import Bits    ( Bits((.&.)) )
-import Int     ( Int32 )
-import PrelBase ( Char#, Char(..) )
+#include "HsVersions.h"
+
+import DATA_INT                ( Int32 )
+import DATA_BITS       ( Bits((.&.)) )
+import Char            ( ord, chr )
 \end{code}
 
 Bit masks
@@ -35,10 +38,11 @@ The predicates below look costly, but aren't, GHC+GCC do a great job
 at the big case below.
 
 \begin{code}
-is_ctype :: Int -> Char# -> Bool
-is_ctype mask c = (fromIntegral (charType (C# c)) .&. fromIntegral mask) /= (0::Int32)
+{-# INLINE is_ctype #-}
+is_ctype :: Int -> Char -> Bool
+is_ctype mask c = (fromIntegral (charType c) .&. fromIntegral mask) /= (0::Int32)
 
-is_ident, is_symbol, is_any, is_space, is_lower, is_upper, is_digit :: Char# -> Bool
+is_ident, is_symbol, is_any, is_space, is_lower, is_upper, is_digit :: Char -> Bool
 is_ident  = is_ctype cIdent
 is_symbol = is_ctype cSymbol
 is_any    = is_ctype cAny
@@ -48,6 +52,28 @@ is_upper  = is_ctype cUpper
 is_digit  = is_ctype cDigit
 \end{code}
 
+Utils
+
+\begin{code}
+hexDigit :: Char -> Int
+hexDigit c | is_digit c = ord c - ord '0'
+           | otherwise  = ord (to_lower c) - ord 'a' + 10
+
+octDecDigit :: Char -> Int
+octDecDigit c = ord c - ord '0'
+
+is_hexdigit c
+       =  is_digit c 
+       || (c >= 'a' && c <= 'f')
+       || (c >= 'A' && c <= 'F')
+
+is_octdigit c = c >= '0' && c <= '7'
+
+to_lower c 
+  | c >=  'A' && c <= 'Z' = chr (ord c - (ord 'A' - ord 'a'))
+  | otherwise = c
+\end{code}
+
 We really mean .|. instead of + below, but GHC currently doesn't do
 any constant folding with bitops. *sigh*
 
@@ -64,7 +90,7 @@ charType c = case c of
    '\7'   -> 0                         -- \007
    '\8'   -> 0                         -- \010
    '\9'   -> cAny + cSpace             -- \t
-   '\10'  -> cAny + cSpace             -- \n
+   '\10'  -> cSpace                   -- \n (not allowed in strings, so !cAny)
    '\11'  -> cAny + cSpace             -- \v
    '\12'  -> cAny + cSpace             -- \f
    '\13'  -> cAny + cSpace             -- ^M