[commit: ghc] master: Revert "Place static closures in their own section." (d5d6fb3)

git at git.haskell.org git at git.haskell.org
Mon Oct 20 23:28:46 UTC 2014


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

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

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

commit d5d6fb340410727345a7b5a47bcf83e7847ea4a3
Author: Edward Z. Yang <ezyang at cs.stanford.edu>
Date:   Mon Oct 20 16:03:50 2014 -0700

    Revert "Place static closures in their own section."
    
    This reverts commit b23ba2a7d612c6b466521399b33fe9aacf5c4f75.
    
    Conflicts:
    	compiler/cmm/PprCmmDecl.hs
    	compiler/nativeGen/PPC/Ppr.hs
    	compiler/nativeGen/SPARC/Ppr.hs
    	compiler/nativeGen/X86/Ppr.hs


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

d5d6fb340410727345a7b5a47bcf83e7847ea4a3
 compiler/cmm/Cmm.hs                  | 1 -
 compiler/cmm/CmmParse.y              | 2 +-
 compiler/cmm/PprCmmDecl.hs           | 1 -
 compiler/codeGen/StgCmmBind.hs       | 4 ++--
 compiler/codeGen/StgCmmCon.hs        | 2 +-
 compiler/codeGen/StgCmmUtils.hs      | 6 ------
 compiler/llvmGen/LlvmCodeGen/Data.hs | 1 -
 compiler/nativeGen/PPC/Ppr.hs        | 1 -
 compiler/nativeGen/SPARC/Ppr.hs      | 1 -
 compiler/nativeGen/X86/Ppr.hs        | 4 ----
 10 files changed, 4 insertions(+), 19 deletions(-)

diff --git a/compiler/cmm/Cmm.hs b/compiler/cmm/Cmm.hs
index 98c5b59..9e9bae9 100644
--- a/compiler/cmm/Cmm.hs
+++ b/compiler/cmm/Cmm.hs
@@ -170,7 +170,6 @@ data Section
   | RelocatableReadOnlyData
   | UninitialisedData
   | ReadOnlyData16      -- .rodata.cst16 on x86_64, 16-byte aligned
-  | StaticClosures
   | OtherSection String
 
 data CmmStatic
diff --git a/compiler/cmm/CmmParse.y b/compiler/cmm/CmmParse.y
index db6cc49..8033330 100644
--- a/compiler/cmm/CmmParse.y
+++ b/compiler/cmm/CmmParse.y
@@ -1105,7 +1105,7 @@ staticClosure :: PackageKey -> FastString -> FastString -> [CmmLit] -> CmmParse
 staticClosure pkg cl_label info payload
   = do dflags <- getDynFlags
        let lits = mkStaticClosure dflags (mkCmmInfoLabel pkg info) dontCareCCS payload [] [] []
-       code $ emitStaticClosure (mkCmmDataLabel pkg cl_label) lits
+       code $ emitDataLits (mkCmmDataLabel pkg cl_label) lits
 
 foreignCall
         :: String
diff --git a/compiler/cmm/PprCmmDecl.hs b/compiler/cmm/PprCmmDecl.hs
index c9bbc8b..87cda6a 100644
--- a/compiler/cmm/PprCmmDecl.hs
+++ b/compiler/cmm/PprCmmDecl.hs
@@ -162,7 +162,6 @@ pprSection s = case s of
     RelocatableReadOnlyData
                       -> section <+> doubleQuotes (text "relreadonly")
     UninitialisedData -> section <+> doubleQuotes (text "uninitialised")
-    StaticClosures    -> section <+> doubleQuotes (text "staticclosures")
     OtherSection s'   -> section <+> doubleQuotes (text s')
  where
     section = ptext (sLit "section")
diff --git a/compiler/codeGen/StgCmmBind.hs b/compiler/codeGen/StgCmmBind.hs
index a253b11..444112f 100644
--- a/compiler/codeGen/StgCmmBind.hs
+++ b/compiler/codeGen/StgCmmBind.hs
@@ -98,7 +98,7 @@ cgTopRhsClosure dflags rec id ccs _ upd_flag args body =
          let closure_rep   = mkStaticClosureFields dflags
                                     indStaticInfoTable ccs MayHaveCafRefs
                                     [unLit (idInfoToAmode cg_info)]
-         emitStaticClosure closure_label closure_rep
+         emitDataLits closure_label closure_rep
          return ()
 
   gen_code dflags lf_info closure_label
@@ -113,7 +113,7 @@ cgTopRhsClosure dflags rec id ccs _ upd_flag args body =
               closure_rep   = mkStaticClosureFields dflags info_tbl ccs caffy []
 
                  -- BUILD THE OBJECT, AND GENERATE INFO TABLE (IF NECESSARY)
-        ; emitStaticClosure closure_label closure_rep
+        ; emitDataLits closure_label closure_rep
         ; let fv_details :: [(NonVoid Id, VirtualHpOffset)]
               (_, _, fv_details) = mkVirtHeapOffsets dflags (isLFThunk lf_info)
                                                (addIdReps [])
diff --git a/compiler/codeGen/StgCmmCon.hs b/compiler/codeGen/StgCmmCon.hs
index 93bfaf0..edd0648 100644
--- a/compiler/codeGen/StgCmmCon.hs
+++ b/compiler/codeGen/StgCmmCon.hs
@@ -101,7 +101,7 @@ cgTopRhsCon dflags id con args =
                              payload
 
                 -- BUILD THE OBJECT
-        ; emitStaticClosure closure_label closure_rep
+        ; emitDataLits closure_label closure_rep
 
         ; return () }
 
diff --git a/compiler/codeGen/StgCmmUtils.hs b/compiler/codeGen/StgCmmUtils.hs
index 8b3616f..d47a016 100644
--- a/compiler/codeGen/StgCmmUtils.hs
+++ b/compiler/codeGen/StgCmmUtils.hs
@@ -12,7 +12,6 @@ module StgCmmUtils (
         cgLit, mkSimpleLit,
         emitDataLits, mkDataLits,
         emitRODataLits, mkRODataLits,
-        emitStaticClosure,
         emitRtsCall, emitRtsCallWithResult, emitRtsCallGen,
         assignTemp, newTemp,
 
@@ -321,11 +320,6 @@ emitRODataLits :: CLabel -> [CmmLit] -> FCode ()
 -- Emit a read-only data block
 emitRODataLits lbl lits = emitDecl (mkRODataLits lbl lits)
 
-emitStaticClosure :: CLabel -> [CmmLit] -> FCode ()
--- Emit a static closure data block, which is only used at startup time.
--- Eventually make this READ ONLY(?)
-emitStaticClosure lbl lits = emitDecl (mkDataLits StaticClosures lbl lits)
-
 newStringCLit :: String -> FCode CmmLit
 -- Make a global definition for the string,
 -- and return its label
diff --git a/compiler/llvmGen/LlvmCodeGen/Data.hs b/compiler/llvmGen/LlvmCodeGen/Data.hs
index 6115b88..1dbfb4b 100644
--- a/compiler/llvmGen/LlvmCodeGen/Data.hs
+++ b/compiler/llvmGen/LlvmCodeGen/Data.hs
@@ -56,7 +56,6 @@ isSecConstant ReadOnlyData            = True
 isSecConstant RelocatableReadOnlyData = True
 isSecConstant ReadOnlyData16          = True
 isSecConstant Data                    = False
-isSecConstant StaticClosures          = False
 isSecConstant UninitialisedData       = False
 isSecConstant (OtherSection _)        = False
 
diff --git a/compiler/nativeGen/PPC/Ppr.hs b/compiler/nativeGen/PPC/Ppr.hs
index 36db75a..e62a1c4 100644
--- a/compiler/nativeGen/PPC/Ppr.hs
+++ b/compiler/nativeGen/PPC/Ppr.hs
@@ -291,7 +291,6 @@ pprSectionHeader seg =
   ReadOnlyData16
    | osDarwin       -> text ".const\n\t.align 4"
    | otherwise      -> text ".section .rodata\n\t.align 4"
-  StaticClosures    -> text ".section staticclosures,\"aw\"\n\t.align 2"
   OtherSection _ ->
       panic "PprMach.pprSectionHeader: unknown section"
 
diff --git a/compiler/nativeGen/SPARC/Ppr.hs b/compiler/nativeGen/SPARC/Ppr.hs
index c0ae9c1..c734687 100644
--- a/compiler/nativeGen/SPARC/Ppr.hs
+++ b/compiler/nativeGen/SPARC/Ppr.hs
@@ -334,7 +334,6 @@ pprSectionHeader seg = case seg of
                     -> text ".text\n\t.align 8"
   UninitialisedData -> text ".bss\n\t.align 8"
   ReadOnlyData16    -> text ".data\n\t.align 16"
-  StaticClosures    -> text ".section staticclosures,\"aw\"\n\t.align 8"
   OtherSection _    -> panic "PprMach.pprSectionHeader: unknown section"
 
 
diff --git a/compiler/nativeGen/X86/Ppr.hs b/compiler/nativeGen/X86/Ppr.hs
index 6449d8e..cc39557 100644
--- a/compiler/nativeGen/X86/Ppr.hs
+++ b/compiler/nativeGen/X86/Ppr.hs
@@ -389,7 +389,6 @@ pprSectionHeader seg =
                         -> text ".const_data\n\t.align 2"
       UninitialisedData -> text ".data\n\t.align 2"
       ReadOnlyData16    -> text ".const\n\t.align 4"
-      StaticClosures    -> text ".section staticclosures,\"aw\"\n\t.align 2"
       OtherSection _    -> panic "X86.Ppr.pprSectionHeader: unknown section"
   | otherwise ->
      case seg of
@@ -400,7 +399,6 @@ pprSectionHeader seg =
                         -> text ".const_data\n\t.align 3"
       UninitialisedData -> text ".data\n\t.align 3"
       ReadOnlyData16    -> text ".const\n\t.align 4"
-      StaticClosures    -> text ".section staticclosures,\"aw\"\n\t.align 3"
       OtherSection _    -> panic "PprMach.pprSectionHeader: unknown section"
  _
   | target32Bit platform ->
@@ -412,7 +410,6 @@ pprSectionHeader seg =
                         -> text ".section .data\n\t.align 4"
       UninitialisedData -> text ".section .bss\n\t.align 4"
       ReadOnlyData16    -> text ".section .rodata\n\t.align 16"
-      StaticClosures    -> text ".section staticclosures,\"aw\"\n\t.align 4"
       OtherSection _    -> panic "X86.Ppr.pprSectionHeader: unknown section"
   | otherwise ->
      case seg of
@@ -423,7 +420,6 @@ pprSectionHeader seg =
                         -> text ".section .data\n\t.align 8"
       UninitialisedData -> text ".section .bss\n\t.align 8"
       ReadOnlyData16    -> text ".section .rodata.cst16\n\t.align 16"
-      StaticClosures    -> text ".section staticclosures,\"aw\"\n\t.align 8"
       OtherSection _    -> panic "PprMach.pprSectionHeader: unknown section"
 
 



More information about the ghc-commits mailing list