Zubin pushed to branch wip/26470 at Glasgow Haskell Compiler / GHC

Commits:

3 changed files:

Changes:

  • compiler/GHC/Parser/Lexer.x
    ... ... @@ -1068,7 +1068,7 @@ reservedWordsFM = listToUFM $
    1068 1068
              ( "mdo",            ITmdo Nothing,   xbit RecursiveDoBit),
    
    1069 1069
                  -- See Note [Lexing type pseudo-keywords]
    
    1070 1070
              ( "family",         ITfamily,        0 ),
    
    1071
    -         ( "role",           ITrole,          0 ),
    
    1071
    +         ( "role",           ITrole,          xbit RoleAnnotationsBit ),
    
    1072 1072
              ( "pattern",        ITpattern,       xbit PatternSynonymsBit),
    
    1073 1073
              ( "static",         ITstatic,        xbit StaticPointersBit ),
    
    1074 1074
              ( "stock",          ITstock,         0 ),
    
    ... ... @@ -2790,6 +2790,7 @@ data ExtBits
    2790 2790
       | RequiredTypeArgumentsBit
    
    2791 2791
       | MultilineStringsBit
    
    2792 2792
       | LevelImportsBit
    
    2793
    +  | RoleAnnotationsBit
    
    2793 2794
     
    
    2794 2795
       -- Flags that are updated once parsing starts
    
    2795 2796
       | InRulePragBit
    
    ... ... @@ -2874,6 +2875,7 @@ mkParserOpts extensionFlags diag_opts
    2874 2875
           .|. RequiredTypeArgumentsBit    `xoptBit` LangExt.RequiredTypeArguments
    
    2875 2876
           .|. MultilineStringsBit         `xoptBit` LangExt.MultilineStrings
    
    2876 2877
           .|. LevelImportsBit             `xoptBit` LangExt.ExplicitLevelImports
    
    2878
    +      .|. RoleAnnotationsBit          `xoptBit` LangExt.RoleAnnotations
    
    2877 2879
         optBits =
    
    2878 2880
               HaddockBit        `setBitIf` isHaddock
    
    2879 2881
           .|. RawTokenStreamBit `setBitIf` rawTokStream
    

  • testsuite/tests/parser/should_compile/T26470.hs
    1
    +{-# LANGUAGE Haskell2010 #-}
    
    2
    +module T26470 where
    
    3
    +
    
    4
    +role :: Int
    
    5
    +role = 42
    
    6
    +
    
    7
    +f :: Int -> Int
    
    8
    +f role = role + 1
    
    9
    +
    
    10
    +data T = MkT { role :: String }
    
    11
    +
    
    12
    +newtype T2 role = MkT2 Int

  • testsuite/tests/parser/should_compile/all.T
    ... ... @@ -208,3 +208,4 @@ test('T25258', normal, compile, [''])
    208 208
     test('T17045b', extra_files(["T17045"]), multimod_compile, ['-iT17045 Test', '-v0'])
    
    209 209
     test('T25900', normal, compile, [''])
    
    210 210
     test('T25900_noext', normal, compile, [''])
    
    211
    +test('T26470', normal, compile, [''])