[commit: ghc] master: Remove unused module (6b032db)

git at git.haskell.org git at git.haskell.org
Tue Aug 20 18:19:51 CEST 2013


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/6b032db4e750c80371d028a9fe384177d6cdf36a/ghc

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

commit 6b032db4e750c80371d028a9fe384177d6cdf36a
Author: Jan Stolarek <jan.stolarek at p.lodz.pl>
Date:   Tue Aug 20 12:50:28 2013 +0100

    Remove unused module
    
    This commit removes module StgCmmGran which has only no-op functions.
    According to comments in the module, it was used by GpH, but GpH
    project seems to be dead for a couple of years now.


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

6b032db4e750c80371d028a9fe384177d6cdf36a
 compiler/codeGen/StgCmmBind.hs |    3 -
 compiler/codeGen/StgCmmGran.hs |  120 ----------------------------------------
 compiler/codeGen/StgCmmHeap.hs |   12 +---
 compiler/ghc.cabal.in          |    1 -
 4 files changed, 2 insertions(+), 134 deletions(-)

diff --git a/compiler/codeGen/StgCmmBind.hs b/compiler/codeGen/StgCmmBind.hs
index ba1e059..516b519 100644
--- a/compiler/codeGen/StgCmmBind.hs
+++ b/compiler/codeGen/StgCmmBind.hs
@@ -22,7 +22,6 @@ import StgCmmCon
 import StgCmmHeap
 import StgCmmProf
 import StgCmmTicky
-import StgCmmGran
 import StgCmmLayout
 import StgCmmUtils
 import StgCmmClosure
@@ -477,7 +476,6 @@ closureCodeBody top_lvl bndr cl_info cc args arity body fv_details
                 ; let node_points = nodeMustPointToIt dflags lf_info
                       node' = if node_points then Just node else Nothing
                 ; when node_points (ldvEnterClosure cl_info)
-                ; granYield arg_regs node_points
 
                 -- Main payload
                 ; entryHeapCheck cl_info node' arity arg_regs $ do
@@ -541,7 +539,6 @@ thunkCode cl_info fv_details _cc node arity body
        ; let node_points = nodeMustPointToIt dflags (closureLFInfo cl_info)
              node'       = if node_points then Just node else Nothing
         ; ldvEnterClosure cl_info -- NB: Node always points when profiling
-        ; granThunk node_points
 
         -- Heap overflow check
         ; entryHeapCheck cl_info node' arity [] $ do
diff --git a/compiler/codeGen/StgCmmGran.hs b/compiler/codeGen/StgCmmGran.hs
deleted file mode 100644
index 91b0c8b..0000000
--- a/compiler/codeGen/StgCmmGran.hs
+++ /dev/null
@@ -1,120 +0,0 @@
------------------------------------------------------------------------------
---
--- (c) The University of Glasgow -2006
---
--- Code generation relaed to GpH
---      (a) parallel
---      (b) GranSim
---
------------------------------------------------------------------------------
-
-module StgCmmGran (
-        staticGranHdr,staticParHdr,
-        granThunk, granYield,
-        doGranAllocate
-  ) where
-
--- This entire module consists of no-op stubs at the moment
--- GranSim worked once, but it certainly doesn't any more
--- I've left the calls, though, in case anyone wants to resurrect it
-
-import StgCmmMonad
-import CmmExpr
-
-staticGranHdr :: [CmmLit]
-staticGranHdr = []
-
-staticParHdr :: [CmmLit]
-staticParHdr = []
-
-doGranAllocate :: VirtualHpOffset -> FCode ()
--- Must be lazy in the amount of allocation
-doGranAllocate _ = return ()
-
-granYield :: [LocalReg] -> Bool -> FCode ()
-granYield _regs _node_reqd = return ()
-
-granThunk :: Bool -> FCode ()
-granThunk _node_points = return ()
-
------------------------------------------------------------------
-{-   ------- Everything below here is commented out -------------
------------------------------------------------------------------
-
--- Parallel header words in a static closure
-staticParHdr :: [CmmLit]
--- Parallel header words in a static closure
-staticParHdr = []
-
-staticGranHdr :: [CmmLit]
--- Gransim header words in a static closure
-staticGranHdr = []
-
-doGranAllocate :: CmmExpr -> Code
--- macro DO_GRAN_ALLOCATE
-doGranAllocate hp
-  | not opt_GranMacros = return ()
-  | otherwise          = panic "doGranAllocate"
-
-
-
--------------------------
-granThunk :: Bool -> FCode ()
--- HWL: insert macros for GrAnSim; 2 versions depending on liveness of node
--- (we prefer fetchAndReschedule-style context switches to yield ones)
-granThunk node_points
-  | node_points = granFetchAndReschedule [] node_points
-  | otherwise   = granYield              [] node_points
-
-granFetchAndReschedule :: [(Id,GlobalReg)]  -- Live registers
-                       -> Bool                  -- Node reqd?
-                       -> Code
--- Emit code for simulating a fetch and then reschedule.
-granFetchAndReschedule regs node_reqd
-  | opt_GranMacros && (node `elem` map snd regs || node_reqd)
-  = do { fetch
-       ; reschedule liveness node_reqd }
-  | otherwise
-  = return ()
-  where
-    liveness = mkRegLiveness regs 0 0
-
-fetch = panic "granFetch"
-        -- Was: absC (CMacroStmt GRAN_FETCH [])
-        --HWL: generate GRAN_FETCH macro for GrAnSim
-        --     currently GRAN_FETCH and GRAN_FETCH_AND_RESCHEDULE are miai
-
-reschedule liveness node_reqd = panic "granReschedule"
-        -- Was: absC  (CMacroStmt GRAN_RESCHEDULE [
-        --                mkIntCLit (I# (word2Int# liveness_mask)),
-        --                mkIntCLit (if node_reqd then 1 else 0)])
-
-
--------------------------
--- The @GRAN_YIELD@ macro is taken from JSM's  code for Concurrent Haskell. It
--- allows to context-switch at  places where @node@ is  not alive (it uses the
--- @Continue@ rather  than the @EnterNodeCode@  function in the  RTS). We emit
--- this kind of macro at the beginning of the following kinds of basic bocks:
--- \begin{itemize}
---  \item Slow entry code where node is not alive (see @StgCmmClosure.lhs@). Normally
---        we use @fetchAndReschedule@ at a slow entry code.
---  \item Fast entry code (see @CgClosure.lhs@).
---  \item Alternatives in case expressions (@CLabelledCode@ structures), provided
---        that they are not inlined (see @CgCases.lhs@). These alternatives will
---        be turned into separate functions.
-
-granYield :: [(Id,GlobalReg)]   -- Live registers
-          -> Bool               -- Node reqd?
-          -> Code
-
-granYield regs node_reqd
-  | opt_GranMacros && node_reqd = yield liveness
-  | otherwise                   = return ()
-  where
-     liveness = mkRegLiveness regs 0 0
-
-yield liveness = panic "granYield"
-        -- Was : absC (CMacroStmt GRAN_YIELD
-        --                  [mkIntCLit (I# (word2Int# liveness_mask))])
-
--}
diff --git a/compiler/codeGen/StgCmmHeap.hs b/compiler/codeGen/StgCmmHeap.hs
index 76c0a4c..97233aa 100644
--- a/compiler/codeGen/StgCmmHeap.hs
+++ b/compiler/codeGen/StgCmmHeap.hs
@@ -30,7 +30,6 @@ import StgCmmUtils
 import StgCmmMonad
 import StgCmmProf
 import StgCmmTicky
-import StgCmmGran
 import StgCmmClosure
 import StgCmmEnv
 
@@ -135,8 +134,7 @@ emitSetDynHdr base info_ptr ccs
   where
     header :: DynFlags -> [CmmExpr]
     header dflags = [info_ptr] ++ dynProfHdr dflags ccs
-        -- ToDo: Gransim stuff
-        -- ToDo: Parallel stuff
+        -- ToDof: Parallel stuff
         -- No ticky header
 
 hpStore :: CmmExpr -> [CmmExpr] -> [VirtualHpOffset] -> FCode ()
@@ -207,16 +205,11 @@ mkStaticClosure :: DynFlags -> CLabel -> CostCentreStack -> [CmmLit]
   -> [CmmLit] -> [CmmLit] -> [CmmLit] -> [CmmLit]
 mkStaticClosure dflags info_lbl ccs payload padding static_link_field saved_info_field
   =  [CmmLabel info_lbl]
-  ++ variable_header_words
+  ++ staticProfHdr dflags ccs
   ++ concatMap (padLitToWord dflags) payload
   ++ padding
   ++ static_link_field
   ++ saved_info_field
-  where
-    variable_header_words
-        =  staticGranHdr
-        ++ staticParHdr
-        ++ staticProfHdr dflags ccs
 
 -- JD: Simon had ellided this padding, but without it the C back end asserts
 -- failure. Maybe it's a bad assertion, and this padding is indeed unnecessary?
@@ -529,7 +522,6 @@ heapCheck checkStack checkYield do_gc code
                       | otherwise  = Nothing
         ; codeOnly $ do_checks stk_hwm checkYield mb_alloc_bytes do_gc
         ; tickyAllocHeap True hpHw
-        ; doGranAllocate hpHw
         ; setRealHp hpHw
         ; code }
 
diff --git a/compiler/ghc.cabal.in b/compiler/ghc.cabal.in
index 0ef2890..bfcbb87 100644
--- a/compiler/ghc.cabal.in
+++ b/compiler/ghc.cabal.in
@@ -208,7 +208,6 @@ Library
         StgCmmEnv
         StgCmmExpr
         StgCmmForeign
-        StgCmmGran
         StgCmmHeap
         StgCmmHpc
         StgCmmArgRep





More information about the ghc-commits mailing list