[commit: ghc] master: Fix startsVarSym and refactor operator predicates (fixes #4239) (f233f00)

git at git.haskell.org git at git.haskell.org
Thu Sep 1 19:05:50 UTC 2016


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/f233f00b1915ac6c0a200b8017a9f07deefd401e/ghc

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

commit f233f00b1915ac6c0a200b8017a9f07deefd401e
Author: Malo Jaffré <jaffre.malo at gmail.com>
Date:   Thu Sep 1 14:13:47 2016 -0400

    Fix startsVarSym and refactor operator predicates (fixes #4239)
    
    startsVarSym used isSymbol which does not recognize valid operators
    beginning with OtherPunctuation generalCategory (e. g. (·)).
    Move it to ghc-boot-th for reducing duplication.
    
    This patch fixes template-haskell pretty printer, which is used by
    -ddump-minimal-imports.
    
    Reviewers: austin, bgamari
    
    Reviewed By: bgamari
    
    Subscribers: thomie
    
    Differential Revision: https://phabricator.haskell.org/D2480
    
    GHC Trac Issues: #4239


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

f233f00b1915ac6c0a200b8017a9f07deefd401e
 compiler/basicTypes/Lexeme.hs                      | 23 ----------------------
 libraries/ghc-boot-th/GHC/Lexeme.hs                | 23 +++++++++++++++++++---
 .../template-haskell/Language/Haskell/TH/Ppr.hs    |  8 +++-----
 testsuite/tests/rename/should_compile/T4239.hs     |  1 +
 testsuite/tests/rename/should_compile/T4239.stdout |  2 +-
 testsuite/tests/rename/should_compile/T4239A.hs    |  1 +
 6 files changed, 26 insertions(+), 32 deletions(-)

diff --git a/compiler/basicTypes/Lexeme.hs b/compiler/basicTypes/Lexeme.hs
index ef5fa12..7012f5a 100644
--- a/compiler/basicTypes/Lexeme.hs
+++ b/compiler/basicTypes/Lexeme.hs
@@ -205,25 +205,6 @@ okIdChar c = case generalCategory c of
   OtherNumber     -> True -- See #4373
   _               -> c == '\'' || c == '_'
 
--- | Is this character acceptable in a symbol (after the first char)?
--- See alexGetByte in Lexer.x
-okSymChar :: Char -> Bool
-okSymChar c
-  | c `elem` specialSymbols
-  = False
-  | c `elem` "_\"'"
-  = False
-  | otherwise
-  = case generalCategory c of
-      ConnectorPunctuation -> True
-      DashPunctuation      -> True
-      OtherPunctuation     -> True
-      MathSymbol           -> True
-      CurrencySymbol       -> True
-      ModifierSymbol       -> True
-      OtherSymbol          -> True
-      _                    -> False
-
 -- | All reserved identifiers. Taken from section 2.4 of the 2010 Report.
 reservedIds :: Set.Set String
 reservedIds = Set.fromList [ "case", "class", "data", "default", "deriving"
@@ -232,10 +213,6 @@ reservedIds = Set.fromList [ "case", "class", "data", "default", "deriving"
                            , "module", "newtype", "of", "then", "type", "where"
                            , "_" ]
 
--- | All punctuation that cannot appear in symbols. See $special in Lexer.x.
-specialSymbols :: [Char]
-specialSymbols = "(),;[]`{}"
-
 -- | All reserved operators. Taken from section 2.4 of the 2010 Report.
 reservedOps :: Set.Set String
 reservedOps = Set.fromList [ "..", ":", "::", "=", "\\", "|", "<-", "->"
diff --git a/libraries/ghc-boot-th/GHC/Lexeme.hs b/libraries/ghc-boot-th/GHC/Lexeme.hs
index 677c9a6..2ecee61 100644
--- a/libraries/ghc-boot-th/GHC/Lexeme.hs
+++ b/libraries/ghc-boot-th/GHC/Lexeme.hs
@@ -11,14 +11,31 @@
 module GHC.Lexeme (
           -- * Lexical characteristics of Haskell names
         startsVarSym, startsVarId, startsConSym, startsConId,
-        startsVarSymASCII, isVarSymChar
+        startsVarSymASCII, isVarSymChar, okSymChar
   ) where
 
 import Data.Char
 
+-- | Is this character acceptable in a symbol (after the first char)?
+-- See alexGetByte in Lexer.x
+okSymChar :: Char -> Bool
+okSymChar c
+  | c `elem` "(),;[]`{}_\"'"
+  = False
+  | otherwise
+  = case generalCategory c of
+      ConnectorPunctuation -> True
+      DashPunctuation      -> True
+      OtherPunctuation     -> True
+      MathSymbol           -> True
+      CurrencySymbol       -> True
+      ModifierSymbol       -> True
+      OtherSymbol          -> True
+      _                    -> False
+
 startsVarSym, startsVarId, startsConSym, startsConId :: Char -> Bool
-startsVarSym c = startsVarSymASCII c || (ord c > 0x7f && isSymbol c)  -- Infix Ids
-startsConSym c = c == ':'               -- Infix data constructors
+startsVarSym c = okSymChar c && c /= ':' -- Infix Ids
+startsConSym c = c == ':'                -- Infix data constructors
 startsVarId c  = c == '_' || case generalCategory c of  -- Ordinary Ids
   LowercaseLetter -> True
   OtherLetter     -> True   -- See #1103
diff --git a/libraries/template-haskell/Language/Haskell/TH/Ppr.hs b/libraries/template-haskell/Language/Haskell/TH/Ppr.hs
index bdd4dd3..0462a8d 100644
--- a/libraries/template-haskell/Language/Haskell/TH/Ppr.hs
+++ b/libraries/template-haskell/Language/Haskell/TH/Ppr.hs
@@ -10,8 +10,9 @@ import Text.PrettyPrint (render)
 import Language.Haskell.TH.PprLib
 import Language.Haskell.TH.Syntax
 import Data.Word ( Word8 )
-import Data.Char ( toLower, chr, ord, isSymbol )
+import Data.Char ( toLower, chr)
 import GHC.Show  ( showMultiLineString )
+import GHC.Lexeme( startsVarSym )
 import Data.Ratio ( numerator, denominator )
 
 nestDepth :: Int
@@ -114,12 +115,9 @@ isSymOcc :: Name -> Bool
 isSymOcc n
   = case nameBase n of
       []    -> True  -- Empty name; weird
-      (c:_) -> isSymbolASCII c || (ord c > 0x7f && isSymbol c)
+      (c:_) -> startsVarSym c
                    -- c.f. OccName.startsVarSym in GHC itself
 
-isSymbolASCII :: Char -> Bool
-isSymbolASCII c = c `elem` "!#$%&*+./<=>?@\\^|~-"
-
 pprInfixExp :: Exp -> Doc
 pprInfixExp (VarE v) = pprName' Infix v
 pprInfixExp (ConE v) = pprName' Infix v
diff --git a/testsuite/tests/rename/should_compile/T4239.hs b/testsuite/tests/rename/should_compile/T4239.hs
index 5d4f94f..02e4128 100644
--- a/testsuite/tests/rename/should_compile/T4239.hs
+++ b/testsuite/tests/rename/should_compile/T4239.hs
@@ -12,3 +12,4 @@ v2 = X
 v3 :: (:+++)
 v3 = (:---)
 
+v4 = (·)
diff --git a/testsuite/tests/rename/should_compile/T4239.stdout b/testsuite/tests/rename/should_compile/T4239.stdout
index 05536b7..6e55a4e 100644
--- a/testsuite/tests/rename/should_compile/T4239.stdout
+++ b/testsuite/tests/rename/should_compile/T4239.stdout
@@ -1 +1 @@
-import T4239A ( type (:+++)((:---), X, (:+++)) )
+import T4239A ( type (:+++)((:---), X, (:+++)), (·) )
diff --git a/testsuite/tests/rename/should_compile/T4239A.hs b/testsuite/tests/rename/should_compile/T4239A.hs
index ea92d96..076f4f2 100644
--- a/testsuite/tests/rename/should_compile/T4239A.hs
+++ b/testsuite/tests/rename/should_compile/T4239A.hs
@@ -8,3 +8,4 @@ data (:+++) = (:+++)
             | X
             | Y
 
+(·) = undefined



More information about the ghc-commits mailing list