Zubin pushed to branch wip/26470 at Glasgow Haskell Compiler / GHC Commits: 7bba4f6e by Zubin Duggal at 2025-10-16T13:33:01+05:30 compiler: "role" is only a keyword when RoleAnnotations is set Fixes #26470 - - - - - 3 changed files: - compiler/GHC/Parser/Lexer.x - + testsuite/tests/parser/should_compile/T26470.hs - testsuite/tests/parser/should_compile/all.T Changes: ===================================== compiler/GHC/Parser/Lexer.x ===================================== @@ -1068,7 +1068,7 @@ reservedWordsFM = listToUFM $ ( "mdo", ITmdo Nothing, xbit RecursiveDoBit), -- See Note [Lexing type pseudo-keywords] ( "family", ITfamily, 0 ), - ( "role", ITrole, 0 ), + ( "role", ITrole, xbit RoleAnnotationsBit ), ( "pattern", ITpattern, xbit PatternSynonymsBit), ( "static", ITstatic, xbit StaticPointersBit ), ( "stock", ITstock, 0 ), @@ -2790,6 +2790,7 @@ data ExtBits | RequiredTypeArgumentsBit | MultilineStringsBit | LevelImportsBit + | RoleAnnotationsBit -- Flags that are updated once parsing starts | InRulePragBit @@ -2874,6 +2875,7 @@ mkParserOpts extensionFlags diag_opts .|. RequiredTypeArgumentsBit `xoptBit` LangExt.RequiredTypeArguments .|. MultilineStringsBit `xoptBit` LangExt.MultilineStrings .|. LevelImportsBit `xoptBit` LangExt.ExplicitLevelImports + .|. RoleAnnotationsBit `xoptBit` LangExt.RoleAnnotations optBits = HaddockBit `setBitIf` isHaddock .|. RawTokenStreamBit `setBitIf` rawTokStream ===================================== testsuite/tests/parser/should_compile/T26470.hs ===================================== @@ -0,0 +1,9 @@ +{-# LANGUAGE Haskell2010 #-} +module T26470 where + +f :: Int -> Int +f role = role + 1 + +data T = MkT { role :: String } + +newtype T2 role = MkT2 Int ===================================== testsuite/tests/parser/should_compile/all.T ===================================== @@ -208,3 +208,4 @@ test('T25258', normal, compile, ['']) test('T17045b', extra_files(["T17045"]), multimod_compile, ['-iT17045 Test', '-v0']) test('T25900', normal, compile, ['']) test('T25900_noext', normal, compile, ['']) +test('T26470', normal, compile, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7bba4f6e12664b48eb4b7a000477718d... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7bba4f6e12664b48eb4b7a000477718d... You're receiving this email because of your account on gitlab.haskell.org.