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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/ee2dad13f8a3cd484f25aa949895535d6eb0f15e

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

commit ee2dad13f8a3cd484f25aa949895535d6eb0f15e
Author: David Waern <[email protected]>
Date:   Fri Nov 25 03:05:32 2011 +0100

    Keep unicode characters in Haddock comments and comments in the token 
stream.

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

 compiler/parser/Lexer.x |   24 ++++++++++++------------
 1 files changed, 12 insertions(+), 12 deletions(-)

diff --git a/compiler/parser/Lexer.x b/compiler/parser/Lexer.x
index 17d3e90..9f2083c 100644
--- a/compiler/parser/Lexer.x
+++ b/compiler/parser/Lexer.x
@@ -785,7 +785,7 @@ ifExtension pred bits _ _ _ = pred bits
 multiline_doc_comment :: Action
 multiline_doc_comment span buf _len = withLexedDocType (worker "")
   where
-    worker commentAcc input docType oneLine = case alexGetChar input of
+    worker commentAcc input docType oneLine = case alexGetChar' input of
       Just ('\n', input')
         | oneLine -> docCommentEnd input commentAcc docType buf span
         | otherwise -> case checkIfCommentLine input' of
@@ -796,15 +796,15 @@ multiline_doc_comment span buf _len = withLexedDocType 
(worker "")
 
     checkIfCommentLine input = check (dropNonNewlineSpace input)
       where
-        check input = case alexGetChar input of
-          Just ('-', input) -> case alexGetChar input of
-            Just ('-', input) -> case alexGetChar input of
+        check input = case alexGetChar' input of
+          Just ('-', input) -> case alexGetChar' input of
+            Just ('-', input) -> case alexGetChar' input of
               Just (c, _) | c /= '-' -> Just input
               _ -> Nothing
             _ -> Nothing
           _ -> Nothing
 
-        dropNonNewlineSpace input = case alexGetChar input of
+        dropNonNewlineSpace input = case alexGetChar' input of
           Just (c, input')
             | isSpace c && c /= '\n' -> dropNonNewlineSpace input'
             | otherwise -> input
@@ -829,13 +829,13 @@ nested_comment cont span _str _len = do
                                if b
                                  then docCommentEnd input commentAcc 
ITblockComment _str span
                                  else cont
-    go commentAcc n input = case alexGetChar input of
+    go commentAcc n input = case alexGetChar' input of
       Nothing -> errBrace input span
-      Just ('-',input) -> case alexGetChar input of
+      Just ('-',input) -> case alexGetChar' input of
         Nothing  -> errBrace input span
         Just ('\125',input) -> go commentAcc (n-1) input
         Just (_,_)          -> go ('-':commentAcc) n input
-      Just ('\123',input) -> case alexGetChar input of
+      Just ('\123',input) -> case alexGetChar' input of
         Nothing  -> errBrace input span
         Just ('-',input) -> go ('-':'\123':commentAcc) (n+1) input
         Just (_,_)       -> go ('\123':commentAcc) n input
@@ -844,14 +844,14 @@ nested_comment cont span _str _len = do
 nested_doc_comment :: Action
 nested_doc_comment span buf _len = withLexedDocType (go "")
   where
-    go commentAcc input docType _ = case alexGetChar input of
+    go commentAcc input docType _ = case alexGetChar' input of
       Nothing -> errBrace input span
-      Just ('-',input) -> case alexGetChar input of
+      Just ('-',input) -> case alexGetChar' input of
         Nothing -> errBrace input span
         Just ('\125',input) ->
           docCommentEnd input commentAcc docType buf span
         Just (_,_) -> go ('-':commentAcc) input docType False
-      Just ('\123', input) -> case alexGetChar input of
+      Just ('\123', input) -> case alexGetChar' input of
         Nothing  -> errBrace input span
         Just ('-',input) -> do
           setInput input
@@ -872,7 +872,7 @@ withLexedDocType lexDocComment = do
     '#' -> lexDocComment input ITdocOptionsOld False
     _ -> panic "withLexedDocType: Bad doc type"
  where
-    lexDocSection n input = case alexGetChar input of
+    lexDocSection n input = case alexGetChar' input of
       Just ('*', input) -> lexDocSection (n+1) input
       Just (_,   _)     -> lexDocComment input (ITdocSection n) True
       Nothing -> do setInput input; lexToken -- eof reached, lex it normally



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

Reply via email to