Repository : ssh://darcs.haskell.org//srv/darcs/ghc

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/59534b8022acf97e9f475cde14b85cd0d74088ac

>---------------------------------------------------------------

commit 59534b8022acf97e9f475cde14b85cd0d74088ac
Author: Simon Marlow <[email protected]>
Date:   Thu Aug 4 15:54:08 2011 +0100

    Update to work with Alex 3.0: basically disabling Alex's new Unicode
    support because we have our own, and defining alexGetByte instead of
    alexGetChar (actually we also define alexGetChar, for backwards
    compatibility).

>---------------------------------------------------------------

 aclocal.m4              |    3 +++
 compiler/cmm/CmmLex.x   |   17 ++++++++++++++---
 compiler/parser/Lexer.x |   15 ++++++++++++---
 mk/config.mk.in         |    7 +++++++
 4 files changed, 36 insertions(+), 6 deletions(-)

diff --git a/aclocal.m4 b/aclocal.m4
index d798eb5..68d3600 100644
--- a/aclocal.m4
+++ b/aclocal.m4
@@ -517,9 +517,12 @@ if test ! -f compiler/cmm/CmmLex.hs || test ! -f 
compiler/parser/Lexer.hs
 then
     FP_COMPARE_VERSIONS([$fptools_cv_alex_version],[-lt],[2.1.0],
       [AC_MSG_ERROR([Alex version 2.1.0 or later is required to compile 
GHC.])])[]
+    FP_COMPARE_VERSIONS([$fptools_cv_alex_version],[-ge],[3.0],
+      [Alex3=YES],[Alex3=NO])
 fi
 AlexVersion=$fptools_cv_alex_version;
 AC_SUBST(AlexVersion)
+AC_SUBST(Alex3)
 ])
 
 
diff --git a/compiler/cmm/CmmLex.x b/compiler/cmm/CmmLex.x
index 9a7b43d..cbadaa8 100644
--- a/compiler/cmm/CmmLex.x
+++ b/compiler/cmm/CmmLex.x
@@ -33,6 +33,9 @@ import FastString
 import Ctype
 import Util
 --import TRACE
+
+import Data.Word
+import Data.Char
 }
 
 $whitechar   = [\ \t\n\r\f\v\xa0] -- \xa0 is Unicode no-break space
@@ -320,11 +323,19 @@ type AlexInput = (RealSrcLoc,StringBuffer)
 alexInputPrevChar :: AlexInput -> Char
 alexInputPrevChar (_,s) = prevChar s '\n'
 
+-- backwards compatibility for Alex 2.x
 alexGetChar :: AlexInput -> Maybe (Char,AlexInput)
-alexGetChar (loc,s) 
+alexGetChar inp = case alexGetByte inp of
+                    Nothing    -> Nothing
+                    Just (b,i) -> c `seq` Just (c,i)
+                       where c = chr $ fromIntegral b
+
+alexGetByte :: AlexInput -> Maybe (Word8,AlexInput)
+alexGetByte (loc,s)
   | atEnd s   = Nothing
-  | otherwise = c `seq` loc' `seq` s' `seq` Just (c, (loc', s'))
-  where c = currentChar s
+  | otherwise = b `seq` loc' `seq` s' `seq` Just (b, (loc', s'))
+  where c    = currentChar s
+        b    = fromIntegral $ ord $ c
         loc' = advanceSrcLoc loc c
        s'   = stepOn s
 
diff --git a/compiler/parser/Lexer.x b/compiler/parser/Lexer.x
index 3f762aa..1570af3 100644
--- a/compiler/parser/Lexer.x
+++ b/compiler/parser/Lexer.x
@@ -80,6 +80,7 @@ import Data.Maybe
 import Data.Map (Map)
 import qualified Data.Map as Map
 import Data.Ratio
+import Data.Word
 }
 
 $unispace    = \x05 -- Trick Alex into handling Unicode. See alexGetChar.
@@ -1576,14 +1577,22 @@ data AlexInput = AI RealSrcLoc StringBuffer
 alexInputPrevChar :: AlexInput -> Char
 alexInputPrevChar (AI _ buf) = prevChar buf '\n'
 
+-- backwards compatibility for Alex 2.x
 alexGetChar :: AlexInput -> Maybe (Char,AlexInput)
-alexGetChar (AI loc s)
+alexGetChar inp = case alexGetByte inp of
+                    Nothing    -> Nothing
+                    Just (b,i) -> c `seq` Just (c,i)
+                       where c = chr $ fromIntegral b
+
+alexGetByte :: AlexInput -> Maybe (Word8,AlexInput)
+alexGetByte (AI loc s)
   | atEnd s   = Nothing
-  | otherwise = adj_c `seq` loc' `seq` s' `seq`
+  | otherwise = byte `seq` loc' `seq` s' `seq`
                 --trace (show (ord c)) $
-                Just (adj_c, (AI loc' s'))
+                Just (byte, (AI loc' s'))
   where (c,s') = nextChar s
         loc'   = advanceSrcLoc loc c
+        byte   = fromIntegral $ ord adj_c
 
         non_graphic     = '\x0'
         upper           = '\x1'
diff --git a/mk/config.mk.in b/mk/config.mk.in
index e39c5c7..0adaf69 100644
--- a/mk/config.mk.in
+++ b/mk/config.mk.in
@@ -760,10 +760,17 @@ SRC_HAPPY_OPTS            = -agc --strict
 #
 ALEX                   = @AlexCmd@
 ALEX_VERSION           = @AlexVersion@         
+Alex3                  = @Alex3@
 #
 # Options to pass to Happy when we're going to compile the output with GHC
 #
+ifeq "$(Alex3)" "YES"
+# We aren't using the Unicode support in Alex 3.0 yet, in fact we do our own
+# Unicode handling, so diable Alex's.
+SRC_ALEX_OPTS          = -g --latin1
+else
 SRC_ALEX_OPTS          = -g
+endif
 
 # Should we build haddock docs?
 HADDOCK_DOCS = YES



_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to