[commit: nofib] master: Remove deprecated _scc_ (#8170) (b9d8bcd)

git at git.haskell.org git
Sat Oct 5 20:52:50 UTC 2013


Repository : ssh://git at git.haskell.org/nofib

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/b9d8bcdd929d664539843f96e56b50800f623891/nofib

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

commit b9d8bcdd929d664539843f96e56b50800f623891
Author: Krzysztof Gogolewski <krz.gogolewski at gmail.com>
Date:   Tue Sep 3 21:23:09 2013 +0200

    Remove deprecated _scc_ (#8170)


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

b9d8bcdd929d664539843f96e56b50800f623891
 fibon/Hackage/Happy/TestInput.y |    4 +---
 parallel/OLD/NESL/fft.lhs       |   10 +++++-----
 real/compress/Lzw2.hs           |   12 ++++++------
 3 files changed, 12 insertions(+), 14 deletions(-)

diff --git a/fibon/Hackage/Happy/TestInput.y b/fibon/Hackage/Happy/TestInput.y
index 95f00ac..34aee2a 100644
--- a/fibon/Hackage/Happy/TestInput.y
+++ b/fibon/Hackage/Happy/TestInput.y
@@ -221,7 +221,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 }
@@ -1296,8 +1295,7 @@ exp10 :: { LHsExpr RdrName }
 	| fexp					{ $1 }
 
 scc_annot :: { Located FastString }
-	: '_scc_' STRING			{ sL (comb2 $1 $>) $ getSTRING $2 }
-	| '{-# SCC' STRING '#-}'		{ sL (comb2 $1 $>) $ getSTRING $2 }
+	: '{-# SCC' STRING '#-}'		{ sL (comb2 $1 $>) $ getSTRING $2 }
 
 hpc_annot :: { Located (FastString,(Int,Int),(Int,Int)) }
 	: '{-# GENERATED' STRING INTEGER ':' INTEGER '-' INTEGER ':' INTEGER '#-}'
diff --git a/parallel/OLD/NESL/fft.lhs b/parallel/OLD/NESL/fft.lhs
index 9beb253..92015d0 100644
--- a/parallel/OLD/NESL/fft.lhs
+++ b/parallel/OLD/NESL/fft.lhs
@@ -48,9 +48,9 @@ two elements (with Haskell's class system that shouldn't be necessary).
 fft :: [Complex Double] -> [Complex Double] -> [Complex Double]
 fft a w  
   | length a <= 1  =  a
-  | otherwise      = let r0 = _scc_ "head"  fft (even_elts a) (even_elts w)
-			 r1 = _scc_ "head"  fft (odd_elts a) (even_elts w)
-                         z =  _scc_ "zip3"  zip3 (r0++r0) (r1++r1) w
+  | otherwise      = let r0 = {-# SCC "head" #-} fft (even_elts a) (even_elts w)
+			 r1 = {-# SCC "head" #-} fft (odd_elts a) (even_elts w)
+                         z =  {-# SCC "zip3" #-}  zip3 (r0++r0) (r1++r1) w
 		     in 
 #if defined(GRAN)
                         parList rnf r0 `par`    
@@ -69,8 +69,8 @@ complex_fft a =
   let 
       c :: Double  
       c = (2.0*pi)/(fromIntegral (length a))
-      w = _scc_ "w"  [ (cos (c*(fromIntegral i)) :+ sin (c*(fromIntegral i)) ) 
-                     | i <- [0..length a] ]
+      w = {-# SCC "w" #-}  [ (cos (c*(fromIntegral i)) :+ sin (c*(fromIntegral i)) ) 
+                           | i <- [0..length a] ]
       -- add = \ (ar,ai) (br,bi) -> (ar+br,ai+bi)
       -- mult = \ (ar,ai) (br,bi) -> (ar*br-ai*bi,ar*bi+ai*br)
   in (rnf w) `seq` fft a w 
diff --git a/real/compress/Lzw2.hs b/real/compress/Lzw2.hs
index 9557407..a0d8cff 100644
--- a/real/compress/Lzw2.hs
+++ b/real/compress/Lzw2.hs
@@ -79,9 +79,9 @@ lzw_code_file input code_table next_code
 code_string :: FAST_INT -> FAST_INT -> [Char] -> PrefixTree -> FAST_TRIPLE;
 
 code_string old_code next_code input@(CBOX(c) : input2) (PT k v t {-p@(PTE k v t)-} l r)
-    | CBOX(c) <  CBOX(k) = _scc_ "cs1" (f1 r1 {-p-} k v t r)
-    | CBOX(c) >  CBOX(k) = _scc_ "cs2" (f2 r2 {-p-} k v t l)
-    | otherwise {- CBOX(c) == CBOX(k) -} = _scc_ "cs3" (f3 r3 k v l r)
+    | CBOX(c) <  CBOX(k) = {-# SCC "cs1" #-} (f1 r1 {-p-} k v t r)
+    | CBOX(c) >  CBOX(k) = {-# SCC "cs2" #-} (f2 r2 {-p-} k v t l)
+    | otherwise {- CBOX(c) == CBOX(k) -} = {-# SCC "cs3" #-} (f3 r3 k v l r)
     where {
         r1 = code_string old_code next_code input  l;
         r2 = code_string old_code next_code input  r;
@@ -94,10 +94,10 @@ code_string old_code next_code input@(CBOX(c) : input2) (PT k v t {-p@(PTE k v t
 
 code_string old_code next_code input@(CBOX(c) : input_file2) PTNil
     =   if (next_code _GE_ ILIT(4096)) 
-        then _scc_ "cs4" _TRIP_(input, old_code, PTNil)
-        else _scc_ "cs5" _TRIP_(input, old_code, PT _PTE_(c, next_code, PTNil) PTNil PTNil);
+        then {-# SCC "cs4" #-} _TRIP_(input, old_code, PTNil)
+        else {-# SCC "cs5" #-} _TRIP_(input, old_code, PT _PTE_(c, next_code, PTNil) PTNil PTNil);
 
-code_string old_code next_code [] code_table = _scc_ "cs6" _TRIP_([], old_code, PTNil);
+code_string old_code next_code [] code_table = {-# SCC "cs6" #-} _TRIP_([], old_code, PTNil);
 
 integer_list_to_char_list (IBOX(n) : l)
     =   CBOX(_CHR_ (n _QUOT_ ILIT(16))) : integer_list_to_char_list2 l n;




More information about the ghc-commits mailing list