diff options
| -rw-r--r-- | compiler/cmm/Cmm.hs | 2 | ||||
| -rw-r--r-- | compiler/cmm/CmmExpr.hs | 1 | ||||
| -rw-r--r-- | compiler/cmm/MkGraph.hs | 19 | ||||
| -rw-r--r-- | compiler/cmm/PprCmmDecl.hs | 3 | ||||
| -rw-r--r-- | compiler/codeGen/CgUtils.hs | 4 | ||||
| -rw-r--r-- | compiler/codeGen/StgCmmBind.hs | 4 | ||||
| -rw-r--r-- | compiler/codeGen/StgCmmExpr.hs | 7 | ||||
| -rw-r--r-- | compiler/codeGen/StgCmmForeign.hs | 4 | ||||
| -rw-r--r-- | compiler/codeGen/StgCmmHeap.hs | 4 | ||||
| -rw-r--r-- | compiler/codeGen/StgCmmMonad.hs | 13 | ||||
| -rw-r--r-- | compiler/codeGen/StgCmmProf.hs | 4 | ||||
| -rw-r--r-- | compiler/codeGen/StgCmmTicky.hs | 4 | 
12 files changed, 19 insertions, 50 deletions
| diff --git a/compiler/cmm/Cmm.hs b/compiler/cmm/Cmm.hs index 9f832731b1..50d48afb38 100644 --- a/compiler/cmm/Cmm.hs +++ b/compiler/cmm/Cmm.hs @@ -1,5 +1,5 @@  -- Cmm representations using Hoopl's Graph CmmNode e x. -{-# LANGUAGE CPP, GADTs #-} +{-# LANGUAGE GADTs #-}  module Cmm (       -- * Cmm top-level datatypes diff --git a/compiler/cmm/CmmExpr.hs b/compiler/cmm/CmmExpr.hs index bae5a739ca..946e146f9e 100644 --- a/compiler/cmm/CmmExpr.hs +++ b/compiler/cmm/CmmExpr.hs @@ -1,5 +1,4 @@  {-# LANGUAGE BangPatterns #-} -{-# LANGUAGE CPP #-}  {-# LANGUAGE FlexibleContexts #-}  {-# LANGUAGE FlexibleInstances #-}  {-# LANGUAGE MultiParamTypeClasses #-} diff --git a/compiler/cmm/MkGraph.hs b/compiler/cmm/MkGraph.hs index d9f140254c..70229d067d 100644 --- a/compiler/cmm/MkGraph.hs +++ b/compiler/cmm/MkGraph.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE BangPatterns, CPP, GADTs #-} +{-# LANGUAGE BangPatterns, GADTs #-}  module MkGraph    ( CmmAGraph, CmmAGraphScoped, CgStmt(..) @@ -21,7 +21,7 @@ module MkGraph    )  where -import GhcPrelude (($),Int,Bool,Eq(..)) -- avoid importing (<*>) +import GhcPrelude hiding ( (<*>) ) -- avoid importing (<*>)  import BlockId  import Cmm @@ -37,10 +37,7 @@ import ForeignCall  import OrdList  import SMRep (ByteOff)  import UniqSupply - -import Control.Monad -import Data.List -import Data.Maybe +import Util  ----------------------------------------------------------------------------- @@ -184,12 +181,10 @@ mkNop        :: CmmAGraph  mkNop         = nilOL  mkComment    :: FastString -> CmmAGraph -#if defined(DEBUG) --- SDM: generating all those comments takes time, this saved about 4% for me -mkComment fs  = mkMiddle $ CmmComment fs -#else -mkComment _   = nilOL -#endif +mkComment fs +  -- SDM: generating all those comments takes time, this saved about 4% for me +  | debugIsOn = mkMiddle $ CmmComment fs +  | otherwise = nilOL  ---------- Assignment and store  mkAssign     :: CmmReg  -> CmmExpr -> CmmAGraph diff --git a/compiler/cmm/PprCmmDecl.hs b/compiler/cmm/PprCmmDecl.hs index 9b3cecc3b8..9dd2332b67 100644 --- a/compiler/cmm/PprCmmDecl.hs +++ b/compiler/cmm/PprCmmDecl.hs @@ -1,5 +1,3 @@ -{-# LANGUAGE CPP #-} -  ----------------------------------------------------------------------------  --  -- Pretty-printing of common Cmm types @@ -54,7 +52,6 @@ import System.IO  -- Temp Jan08  import SMRep -#include "../includes/rts/storage/FunTypes.h"  pprCmms :: (Outputable info, Outputable g) diff --git a/compiler/codeGen/CgUtils.hs b/compiler/codeGen/CgUtils.hs index c20f1fd1d0..6a2840294a 100644 --- a/compiler/codeGen/CgUtils.hs +++ b/compiler/codeGen/CgUtils.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE CPP, GADTs #-} +{-# LANGUAGE GADTs #-}  -----------------------------------------------------------------------------  -- @@ -10,8 +10,6 @@  module CgUtils ( fixStgRegisters ) where -#include "HsVersions.h" -  import GhcPrelude  import CodeGen.Platform diff --git a/compiler/codeGen/StgCmmBind.hs b/compiler/codeGen/StgCmmBind.hs index 9ef552d336..b29394da6f 100644 --- a/compiler/codeGen/StgCmmBind.hs +++ b/compiler/codeGen/StgCmmBind.hs @@ -1,5 +1,3 @@ -{-# LANGUAGE CPP #-} -  -----------------------------------------------------------------------------  --  -- Stg to C-- code generation: bindings @@ -15,8 +13,6 @@ module StgCmmBind (          pushUpdateFrame, emitUpdateFrame    ) where -#include "HsVersions.h" -  import GhcPrelude hiding ((<*>))  import StgCmmExpr diff --git a/compiler/codeGen/StgCmmExpr.hs b/compiler/codeGen/StgCmmExpr.hs index 3fcc935121..c2f2efed3d 100644 --- a/compiler/codeGen/StgCmmExpr.hs +++ b/compiler/codeGen/StgCmmExpr.hs @@ -1,5 +1,4 @@  {-# LANGUAGE CPP #-} -{-# OPTIONS_GHC -fno-warn-unused-do-bind #-}  -----------------------------------------------------------------------------  -- @@ -409,7 +408,8 @@ cgCase (StgApp v []) bndr alt_type@(PrimAlt _) alts         ; v_info <- getCgIdInfo v         ; emitAssign (CmmLocal (idToReg dflags (NonVoid bndr)))                      (idInfoToAmode v_info) -       ; bindArgToReg (NonVoid bndr) +       -- Add bndr to the environment +       ; _ <- bindArgToReg (NonVoid bndr)         ; cgAlts (NoGcInAlts,AssignedDirectly) (NonVoid bndr) alt_type alts }    where      reps_compatible = ((==) `on` (primRepSlot . idPrimRep)) v bndr @@ -435,7 +435,8 @@ it would be better to invoke some kind of panic function here.  cgCase scrut@(StgApp v []) _ (PrimAlt _) _    = do { dflags <- getDynFlags         ; mb_cc <- maybeSaveCostCentre True -       ; withSequel (AssignTo [idToReg dflags (NonVoid v)] False) (cgExpr scrut) +       ; _ <- withSequel +                  (AssignTo [idToReg dflags (NonVoid v)] False) (cgExpr scrut)         ; restoreCurrentCostCentre mb_cc         ; emitComment $ mkFastString "should be unreachable code"         ; l <- newBlockId diff --git a/compiler/codeGen/StgCmmForeign.hs b/compiler/codeGen/StgCmmForeign.hs index d0ad17f59b..b518c0790a 100644 --- a/compiler/codeGen/StgCmmForeign.hs +++ b/compiler/codeGen/StgCmmForeign.hs @@ -1,5 +1,3 @@ -{-# LANGUAGE CPP #-} -  -----------------------------------------------------------------------------  --  -- Code generation for foreign calls. @@ -20,8 +18,6 @@ module StgCmmForeign (    emitCloseNursery,   ) where -#include "HsVersions.h" -  import GhcPrelude hiding( succ, (<*>) )  import StgSyn diff --git a/compiler/codeGen/StgCmmHeap.hs b/compiler/codeGen/StgCmmHeap.hs index 07633ed4ae..3be35b35fa 100644 --- a/compiler/codeGen/StgCmmHeap.hs +++ b/compiler/codeGen/StgCmmHeap.hs @@ -1,5 +1,3 @@ -{-# LANGUAGE CPP #-} -  -----------------------------------------------------------------------------  --  -- Stg to C--: heap management functions @@ -22,8 +20,6 @@ module StgCmmHeap (          emitSetDynHdr      ) where -#include "HsVersions.h" -  import GhcPrelude hiding ((<*>))  import StgSyn diff --git a/compiler/codeGen/StgCmmMonad.hs b/compiler/codeGen/StgCmmMonad.hs index 7c3864296c..cc941a2e57 100644 --- a/compiler/codeGen/StgCmmMonad.hs +++ b/compiler/codeGen/StgCmmMonad.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE CPP, GADTs, UnboxedTuples #-} +{-# LANGUAGE GADTs, UnboxedTuples #-}  -----------------------------------------------------------------------------  -- @@ -58,8 +58,6 @@ module StgCmmMonad (          CgInfoDownwards(..), CgState(..)        -- non-abstract      ) where -#include "HsVersions.h" -  import GhcPrelude hiding( sequence, succ )  import Cmm @@ -79,6 +77,7 @@ import Unique  import UniqSupply  import FastString  import Outputable +import Util  import Control.Monad  import Data.List @@ -696,11 +695,9 @@ emitLabel id = do tscope <- getTickScope                    emitCgStmt (CgLabel id tscope)  emitComment :: FastString -> FCode () -#if 0 /* def DEBUG */ -emitComment s = emitCgStmt (CgStmt (CmmComment s)) -#else -emitComment _ = return () -#endif +emitComment s +  | debugIsOn = emitCgStmt (CgStmt (CmmComment s)) +  | otherwise = return ()  emitTick :: CmmTickish -> FCode ()  emitTick = emitCgStmt . CgStmt . CmmTick diff --git a/compiler/codeGen/StgCmmProf.hs b/compiler/codeGen/StgCmmProf.hs index a0bca5d661..15c31ca59c 100644 --- a/compiler/codeGen/StgCmmProf.hs +++ b/compiler/codeGen/StgCmmProf.hs @@ -1,5 +1,3 @@ -{-# LANGUAGE CPP #-} -  -----------------------------------------------------------------------------  --  -- Code generation for profiling @@ -25,8 +23,6 @@ module StgCmmProf (          ldvEnter, ldvEnterClosure, ldvRecordCreate    ) where -#include "HsVersions.h" -  import GhcPrelude  import StgCmmClosure diff --git a/compiler/codeGen/StgCmmTicky.hs b/compiler/codeGen/StgCmmTicky.hs index a7d158ce3a..8f3074856a 100644 --- a/compiler/codeGen/StgCmmTicky.hs +++ b/compiler/codeGen/StgCmmTicky.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE BangPatterns, CPP #-} +{-# LANGUAGE BangPatterns #-}  -----------------------------------------------------------------------------  -- @@ -104,8 +104,6 @@ module StgCmmTicky (    tickySlowCall, tickySlowCallPat,    ) where -#include "HsVersions.h" -  import GhcPrelude  import StgCmmArgRep    ( slowCallPattern , toArgRep , argRepString ) | 
