[commit: ghc] master: Improve error when using forall with UnicodeSyntax (96adf0e)

git at git.haskell.org git at git.haskell.org
Mon Aug 19 06:16:45 CEST 2013


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

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

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

commit 96adf0e99b1a6595ee40ef9c05263a4fe73eb7c5
Author: Austin Seipp <aseipp at pobox.com>
Date:   Sun Aug 18 23:01:57 2013 -0500

    Improve error when using forall with UnicodeSyntax
    
    Fixes Trac #7901.
    
    '∀' is neither upper nor lowercase, unlike the 'f' in 'forall', so when
    explicit forall is not enabled, it creates a parse error before reaching
    the '.', which is where we give a nice message for ascii 'forall'.
    Therefore, we make '∀' into a token as long as UnicodeSyntax is enabled,
    which is safe because its caselessness means it can never be mistaken
    for a symbol, and check extensions in the parser when the 'forall' rule
    is used.
    
    Authored-by: Paul Cavallaro <ptc at fb.com>
    Authored-by: Anders Papitto <anderspapitto at gmail.com>
    Signed-off-by: Austin Seipp <aseipp at pobox.com>


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

96adf0e99b1a6595ee40ef9c05263a4fe73eb7c5
 compiler/parser/Lexer.x     |    9 +++++----
 compiler/parser/Parser.y.pp |   17 +++++++++++++++--
 2 files changed, 20 insertions(+), 6 deletions(-)

diff --git a/compiler/parser/Lexer.x b/compiler/parser/Lexer.x
index 4a64069..9588094 100644
--- a/compiler/parser/Lexer.x
+++ b/compiler/parser/Lexer.x
@@ -57,6 +57,8 @@ module Lexer (
    extension, bangPatEnabled, datatypeContextsEnabled,
    traditionalRecordSyntaxEnabled,
    typeLiteralsEnabled,
+   explicitForallEnabled,
+   inRulePrag,
    explicitNamespacesEnabled, sccProfilingOn, hpcEnabled,
    addWarning,
    lexTokenStream
@@ -711,8 +713,7 @@ reservedSymsFM = listToUFM $
 
        ,("∷",   ITdcolon, unicodeSyntaxEnabled)
        ,("⇒",   ITdarrow, unicodeSyntaxEnabled)
-       ,("∀",   ITforall, \i -> unicodeSyntaxEnabled i &&
-                                explicitForallEnabled i)
+       ,("∀",   ITforall, unicodeSyntaxEnabled)
        ,("→",   ITrarrow, unicodeSyntaxEnabled)
        ,("←",   ITlarrow, unicodeSyntaxEnabled)
 
@@ -1931,8 +1932,8 @@ datatypeContextsEnabled :: Int -> Bool
 datatypeContextsEnabled flags = testBit flags datatypeContextsBit
 qqEnabled :: Int -> Bool
 qqEnabled        flags = testBit flags qqBit
--- inRulePrag :: Int -> Bool
--- inRulePrag       flags = testBit flags inRulePragBit
+inRulePrag :: Int -> Bool
+inRulePrag       flags = testBit flags inRulePragBit
 rawTokenStreamEnabled :: Int -> Bool
 rawTokenStreamEnabled flags = testBit flags rawTokenStreamBit
 alternativeLayoutRule :: Int -> Bool
diff --git a/compiler/parser/Parser.y.pp b/compiler/parser/Parser.y.pp
index 384fb53..9d08706 100644
--- a/compiler/parser/Parser.y.pp
+++ b/compiler/parser/Parser.y.pp
@@ -1050,7 +1050,8 @@ strict_mark :: { Located HsBang }
 
 -- A ctype is a for-all type
 ctype   :: { LHsType RdrName }
-        : 'forall' tv_bndrs '.' ctype   { LL $ mkExplicitHsForAllTy $2 (noLoc []) $4 }
+        : 'forall' tv_bndrs '.' ctype   {% hintExplicitForall (getLoc $1) >>
+                                            return (LL $ mkExplicitHsForAllTy $2 (noLoc []) $4) }
         | context '=>' ctype            { LL $ mkImplicitHsForAllTy   $1 $3 }
         -- A type of form (context => type) is an *implicit* HsForAllTy
         | ipvar '::' type               { LL (HsIParamTy (unLoc $1) $3) }
@@ -1068,7 +1069,8 @@ ctype   :: { LHsType RdrName }
 -- to 'field' or to 'Int'. So we must use `ctype` to describe the type.
 
 ctypedoc :: { LHsType RdrName }
-        : 'forall' tv_bndrs '.' ctypedoc        { LL $ mkExplicitHsForAllTy $2 (noLoc []) $4 }
+        : 'forall' tv_bndrs '.' ctypedoc {% hintExplicitForall (getLoc $1) >>
+                                            return (LL $ mkExplicitHsForAllTy $2 (noLoc []) $4) }
         | context '=>' ctypedoc         { LL $ mkImplicitHsForAllTy   $1 $3 }
         -- A type of form (context => type) is an *implicit* HsForAllTy
         | ipvar '::' type               { LL (HsIParamTy (unLoc $1) $3) }
@@ -2240,4 +2242,15 @@ hintMultiWayIf span = do
   mwiEnabled <- liftM ((Opt_MultiWayIf `xopt`) . dflags) getPState
   unless mwiEnabled $ parseErrorSDoc span $
     text "Multi-way if-expressions need -XMultiWayIf turned on"
+
+-- Hint about explicit-forall, assuming UnicodeSyntax is on
+hintExplicitForall :: SrcSpan -> P ()
+hintExplicitForall span = do
+    forall      <- extension explicitForallEnabled
+    rulePrag    <- extension inRulePrag
+    unless (forall || rulePrag) $ parseErrorSDoc span $ vcat
+      [ text "Illegal symbol '∀' in type"
+      , text "Perhaps you intended -XRankNTypes or similar flag"
+      , text "to enable explicit-forall syntax: ∀ <tvs>. <type>"
+      ]
 }





More information about the ghc-commits mailing list