[commit: ghc] master: Add comment about lexing of INLINE and INLINABLE pragma (2f79e79)
git at git.haskell.org
git at git.haskell.org
Wed Aug 3 10:30:01 UTC 2016
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/2f79e79ca367b438a2eb60711784b862b1077dae/ghc
>---------------------------------------------------------------
commit 2f79e79ca367b438a2eb60711784b862b1077dae
Author: Matthew Pickering <matthewtpickering at gmail.com>
Date: Wed Aug 3 11:29:26 2016 +0100
Add comment about lexing of INLINE and INLINABLE pragma
>---------------------------------------------------------------
2f79e79ca367b438a2eb60711784b862b1077dae
compiler/parser/Parser.y | 3 ++-
1 file changed, 2 insertions(+), 1 deletion(-)
diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y
index cd10a29..b9479d9 100644
--- a/compiler/parser/Parser.y
+++ b/compiler/parser/Parser.y
@@ -369,7 +369,7 @@ output it generates.
'pattern' { L _ ITpattern } -- for pattern synonyms
'static' { L _ ITstatic } -- for static pointers extension
- '{-# INLINE' { L _ (ITinline_prag _ _ _) }
+ '{-# INLINE' { L _ (ITinline_prag _ _ _) } -- INLINE or INLINABLE
'{-# SPECIALISE' { L _ (ITspec_prag _) }
'{-# SPECIALISE_INLINE' { L _ (ITspec_inline_prag _ _) }
'{-# SOURCE' { L _ (ITsource_prag _) }
@@ -2058,6 +2058,7 @@ sigdecl :: { LHsDecl RdrName }
| pattern_synonym_sig { sLL $1 $> . SigD . unLoc $ $1 }
+ -- This rule is for both INLINE and INLINABLE pragmas
| '{-# INLINE' activation qvar '#-}'
{% ams ((sLL $1 $> $ SigD (InlineSig $3
(mkInlinePragma (getINLINE_PRAGs $1) (getINLINE $1)
More information about the ghc-commits
mailing list