[commit: ghc] master: Remove deprecated _scc_ (#8170) (3e0109b)
git at git.haskell.org
git
Sat Oct 5 20:47:10 UTC 2013
Repository : ssh://git at git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/3e0109b302bbd9f849d71cbc3efcc905d5271e4e/ghc
>---------------------------------------------------------------
commit 3e0109b302bbd9f849d71cbc3efcc905d5271e4e
Author: Krzysztof Gogolewski <krz.gogolewski at gmail.com>
Date: Sat Aug 24 16:40:06 2013 +0200
Remove deprecated _scc_ (#8170)
>---------------------------------------------------------------
3e0109b302bbd9f849d71cbc3efcc905d5271e4e
compiler/hsSyn/HsExpr.lhs | 2 +-
compiler/parser/Lexer.x | 1 -
compiler/parser/Parser.y.pp | 5 +----
compiler/stranal/WwLib.lhs | 6 +++---
rts/Profiling.c | 2 +-
5 files changed, 6 insertions(+), 10 deletions(-)
diff --git a/compiler/hsSyn/HsExpr.lhs b/compiler/hsSyn/HsExpr.lhs
index 2627f7f..4b62b15 100644
--- a/compiler/hsSyn/HsExpr.lhs
+++ b/compiler/hsSyn/HsExpr.lhs
@@ -593,7 +593,7 @@ ppr_expr (EAsPat v e) = ppr v <> char '@' <> pprParendExpr e
ppr_expr (EViewPat p e) = ppr p <+> ptext (sLit "->") <+> ppr e
ppr_expr (HsSCC lbl expr)
- = sep [ ptext (sLit "_scc_") <+> doubleQuotes (ftext lbl),
+ = sep [ ptext (sLit "{-# SCC") <+> doubleQuotes (ftext lbl) <+> ptext (sLit "#-}"),
pprParendExpr expr ]
ppr_expr (HsWrap co_fn e) = pprHsWrapper (pprExpr e) co_fn
diff --git a/compiler/parser/Lexer.x b/compiler/parser/Lexer.x
index 9d4fe1c..18a9e53 100644
--- a/compiler/parser/Lexer.x
+++ b/compiler/parser/Lexer.x
@@ -660,7 +660,6 @@ reservedWordsFM = listToUFM $
( "then", ITthen, 0 ),
( "type", ITtype, 0 ),
( "where", ITwhere, 0 ),
- ( "_scc_", ITscc, 0 ), -- ToDo: remove
( "forall", ITforall, bit explicitForallBit .|.
bit inRulePragBit),
diff --git a/compiler/parser/Parser.y.pp b/compiler/parser/Parser.y.pp
index b520d62..b74d55d 100644
--- a/compiler/parser/Parser.y.pp
+++ b/compiler/parser/Parser.y.pp
@@ -227,7 +227,6 @@ incorrect.
'then' { L _ ITthen }
'type' { L _ ITtype }
'where' { L _ ITwhere }
- '_scc_' { L _ ITscc } -- ToDo: remove
'forall' { L _ ITforall } -- GHC extension keywords
'foreign' { L _ ITforeign }
@@ -1504,9 +1503,7 @@ optSemi :: { Bool }
| {- empty -} { False }
scc_annot :: { Located FastString }
- : '_scc_' STRING {% (addWarning Opt_WarnWarningsDeprecations (getLoc $1) (text "_scc_ is deprecated; use an SCC pragma instead")) >>= \_ ->
- ( do scc <- getSCC $2; return $ LL scc ) }
- | '{-# SCC' STRING '#-}' {% do scc <- getSCC $2; return $ LL scc }
+ : '{-# SCC' STRING '#-}' {% do scc <- getSCC $2; return $ LL scc }
| '{-# SCC' VARID '#-}' { LL (getVARID $2) }
hpc_annot :: { Located (FastString,(Int,Int),(Int,Int)) }
diff --git a/compiler/stranal/WwLib.lhs b/compiler/stranal/WwLib.lhs
index c0c3f6c..711a558 100644
--- a/compiler/stranal/WwLib.lhs
+++ b/compiler/stranal/WwLib.lhs
@@ -591,12 +591,12 @@ mkUnpackCase scrut uniq boxing_con unpk_args body
Note [Profiling and unpacking]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
If the original function looked like
- f = \ x -> _scc_ "foo" E
+ f = \ x -> {-# SCC "foo" #-} E
then we want the CPR'd worker to look like
- \ x -> _scc_ "foo" (case E of I# x -> x)
+ \ x -> {-# SCC "foo" #-} (case E of I# x -> x)
and definitely not
- \ x -> case (_scc_ "foo" E) of I# x -> x)
+ \ x -> case ({-# SCC "foo" #-} E) of I# x -> x)
This transform doesn't move work or allocation
from one cost centre to another.
diff --git a/rts/Profiling.c b/rts/Profiling.c
index 0c67326..50c9c39 100644
--- a/rts/Profiling.c
+++ b/rts/Profiling.c
@@ -66,7 +66,7 @@ Mutex ccs_mutex;
* Built-in cost centres and cost-centre stacks:
*
* MAIN is the root of the cost-centre stack tree. If there are
- * no _scc_s in the program, all costs will be attributed
+ * no {-# SCC #-}s in the program, all costs will be attributed
* to MAIN.
*
* SYSTEM is the RTS in general (scheduler, etc.). All costs for
More information about the ghc-commits
mailing list