summaryrefslogtreecommitdiff
path: root/compiler/codeGen
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/codeGen')
-rw-r--r--compiler/codeGen/CgUtils.hs3
-rw-r--r--compiler/codeGen/CodeGen/Platform/ARM.hs1
-rw-r--r--compiler/codeGen/CodeGen/Platform/NoRegs.hs1
-rw-r--r--compiler/codeGen/CodeGen/Platform/PPC.hs1
-rw-r--r--compiler/codeGen/CodeGen/Platform/PPC_Darwin.hs1
-rw-r--r--compiler/codeGen/CodeGen/Platform/SPARC.hs1
-rw-r--r--compiler/codeGen/CodeGen/Platform/X86.hs1
-rw-r--r--compiler/codeGen/CodeGen/Platform/X86_64.hs1
-rw-r--r--compiler/codeGen/StgCmm.hs7
-rw-r--r--compiler/codeGen/StgCmmBind.hs2
-rw-r--r--compiler/codeGen/StgCmmClosure.hs4
-rw-r--r--compiler/codeGen/StgCmmCon.hs2
-rw-r--r--compiler/codeGen/StgCmmEnv.hs2
-rw-r--r--compiler/codeGen/StgCmmExpr.hs2
-rw-r--r--compiler/codeGen/StgCmmForeign.hs2
-rw-r--r--compiler/codeGen/StgCmmHeap.hs2
-rw-r--r--compiler/codeGen/StgCmmLayout.hs2
-rw-r--r--compiler/codeGen/StgCmmMonad.hs3
-rw-r--r--compiler/codeGen/StgCmmPrim.hs96
-rw-r--r--compiler/codeGen/StgCmmProf.hs2
-rw-r--r--compiler/codeGen/StgCmmTicky.hs2
-rw-r--r--compiler/codeGen/StgCmmUtils.hs2
22 files changed, 132 insertions, 8 deletions
diff --git a/compiler/codeGen/CgUtils.hs b/compiler/codeGen/CgUtils.hs
index 6b36ab09cd..51b8ed9ec8 100644
--- a/compiler/codeGen/CgUtils.hs
+++ b/compiler/codeGen/CgUtils.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE CPP, GADTs #-}
+
-----------------------------------------------------------------------------
--
-- Code generator utilities; mostly monadic
@@ -6,7 +8,6 @@
--
-----------------------------------------------------------------------------
-{-# LANGUAGE GADTs #-}
module CgUtils ( fixStgRegisters ) where
#include "HsVersions.h"
diff --git a/compiler/codeGen/CodeGen/Platform/ARM.hs b/compiler/codeGen/CodeGen/Platform/ARM.hs
index 727a43561f..5d1148496c 100644
--- a/compiler/codeGen/CodeGen/Platform/ARM.hs
+++ b/compiler/codeGen/CodeGen/Platform/ARM.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE CPP #-}
module CodeGen.Platform.ARM where
diff --git a/compiler/codeGen/CodeGen/Platform/NoRegs.hs b/compiler/codeGen/CodeGen/Platform/NoRegs.hs
index c4c63b7572..0c85ffbda7 100644
--- a/compiler/codeGen/CodeGen/Platform/NoRegs.hs
+++ b/compiler/codeGen/CodeGen/Platform/NoRegs.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE CPP #-}
module CodeGen.Platform.NoRegs where
diff --git a/compiler/codeGen/CodeGen/Platform/PPC.hs b/compiler/codeGen/CodeGen/Platform/PPC.hs
index bcbdfe244b..76a2b020ac 100644
--- a/compiler/codeGen/CodeGen/Platform/PPC.hs
+++ b/compiler/codeGen/CodeGen/Platform/PPC.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE CPP #-}
module CodeGen.Platform.PPC where
diff --git a/compiler/codeGen/CodeGen/Platform/PPC_Darwin.hs b/compiler/codeGen/CodeGen/Platform/PPC_Darwin.hs
index 42bf22f26c..a98e558cc1 100644
--- a/compiler/codeGen/CodeGen/Platform/PPC_Darwin.hs
+++ b/compiler/codeGen/CodeGen/Platform/PPC_Darwin.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE CPP #-}
module CodeGen.Platform.PPC_Darwin where
diff --git a/compiler/codeGen/CodeGen/Platform/SPARC.hs b/compiler/codeGen/CodeGen/Platform/SPARC.hs
index b49af14409..991f515eaf 100644
--- a/compiler/codeGen/CodeGen/Platform/SPARC.hs
+++ b/compiler/codeGen/CodeGen/Platform/SPARC.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE CPP #-}
module CodeGen.Platform.SPARC where
diff --git a/compiler/codeGen/CodeGen/Platform/X86.hs b/compiler/codeGen/CodeGen/Platform/X86.hs
index 6dd74df130..e74807ff88 100644
--- a/compiler/codeGen/CodeGen/Platform/X86.hs
+++ b/compiler/codeGen/CodeGen/Platform/X86.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE CPP #-}
module CodeGen.Platform.X86 where
diff --git a/compiler/codeGen/CodeGen/Platform/X86_64.hs b/compiler/codeGen/CodeGen/Platform/X86_64.hs
index 190d642ea6..102132d679 100644
--- a/compiler/codeGen/CodeGen/Platform/X86_64.hs
+++ b/compiler/codeGen/CodeGen/Platform/X86_64.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE CPP #-}
module CodeGen.Platform.X86_64 where
diff --git a/compiler/codeGen/StgCmm.hs b/compiler/codeGen/StgCmm.hs
index a92f80439b..efc89fe04a 100644
--- a/compiler/codeGen/StgCmm.hs
+++ b/compiler/codeGen/StgCmm.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE CPP #-}
+
-----------------------------------------------------------------------------
--
-- Stg to C-- code generation
@@ -37,7 +39,6 @@ import DataCon
import Name
import TyCon
import Module
-import ErrUtils
import Outputable
import Stream
import BasicTypes
@@ -60,9 +61,7 @@ codeGen :: DynFlags
codeGen dflags this_mod data_tycons
cost_centre_info stg_binds hpc_info
- = do { liftIO $ showPass dflags "New CodeGen"
-
- -- cg: run the code generator, and yield the resulting CmmGroup
+ = do { -- cg: run the code generator, and yield the resulting CmmGroup
-- Using an IORef to store the state is a bit crude, but otherwise
-- we would need to add a state monad layer.
; cgref <- liftIO $ newIORef =<< initC
diff --git a/compiler/codeGen/StgCmmBind.hs b/compiler/codeGen/StgCmmBind.hs
index 06e17164dd..4631b2dc14 100644
--- a/compiler/codeGen/StgCmmBind.hs
+++ b/compiler/codeGen/StgCmmBind.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE CPP #-}
+
-----------------------------------------------------------------------------
--
-- Stg to C-- code generation: bindings
diff --git a/compiler/codeGen/StgCmmClosure.hs b/compiler/codeGen/StgCmmClosure.hs
index c9302f21a1..b65d56bae2 100644
--- a/compiler/codeGen/StgCmmClosure.hs
+++ b/compiler/codeGen/StgCmmClosure.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE CPP, RecordWildCards #-}
+
-----------------------------------------------------------------------------
--
-- Stg to C-- code generation:
@@ -9,8 +11,6 @@
--
-----------------------------------------------------------------------------
-{-# LANGUAGE RecordWildCards #-}
-
module StgCmmClosure (
DynTag, tagForCon, isSmallFamily,
ConTagZ, dataConTagZ,
diff --git a/compiler/codeGen/StgCmmCon.hs b/compiler/codeGen/StgCmmCon.hs
index a02a5da616..1a69927b5c 100644
--- a/compiler/codeGen/StgCmmCon.hs
+++ b/compiler/codeGen/StgCmmCon.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE CPP #-}
+
-----------------------------------------------------------------------------
--
-- Stg to C--: code generation for constructors
diff --git a/compiler/codeGen/StgCmmEnv.hs b/compiler/codeGen/StgCmmEnv.hs
index 2b8677c408..4127b67401 100644
--- a/compiler/codeGen/StgCmmEnv.hs
+++ b/compiler/codeGen/StgCmmEnv.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE CPP #-}
+
-----------------------------------------------------------------------------
--
-- Stg to C-- code generation: the binding environment
diff --git a/compiler/codeGen/StgCmmExpr.hs b/compiler/codeGen/StgCmmExpr.hs
index 9b9d6397c4..ad34b5ba19 100644
--- a/compiler/codeGen/StgCmmExpr.hs
+++ b/compiler/codeGen/StgCmmExpr.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE CPP #-}
+
-----------------------------------------------------------------------------
--
-- Stg to C-- code generation: expressions
diff --git a/compiler/codeGen/StgCmmForeign.hs b/compiler/codeGen/StgCmmForeign.hs
index bf88f1ccb3..6937c85d01 100644
--- a/compiler/codeGen/StgCmmForeign.hs
+++ b/compiler/codeGen/StgCmmForeign.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE CPP #-}
+
-----------------------------------------------------------------------------
--
-- Code generation for foreign calls.
diff --git a/compiler/codeGen/StgCmmHeap.hs b/compiler/codeGen/StgCmmHeap.hs
index a3a47a65e7..d00dc6ec84 100644
--- a/compiler/codeGen/StgCmmHeap.hs
+++ b/compiler/codeGen/StgCmmHeap.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE CPP #-}
+
-----------------------------------------------------------------------------
--
-- Stg to C--: heap management functions
diff --git a/compiler/codeGen/StgCmmLayout.hs b/compiler/codeGen/StgCmmLayout.hs
index a56248dcb9..99e926c987 100644
--- a/compiler/codeGen/StgCmmLayout.hs
+++ b/compiler/codeGen/StgCmmLayout.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE CPP #-}
+
-----------------------------------------------------------------------------
--
-- Building info tables.
diff --git a/compiler/codeGen/StgCmmMonad.hs b/compiler/codeGen/StgCmmMonad.hs
index 348b7b9299..cad261bcfb 100644
--- a/compiler/codeGen/StgCmmMonad.hs
+++ b/compiler/codeGen/StgCmmMonad.hs
@@ -1,4 +1,5 @@
-{-# LANGUAGE GADTs #-}
+{-# LANGUAGE CPP, GADTs, UnboxedTuples #-}
+
-----------------------------------------------------------------------------
--
-- Monad for Stg to C-- code generation
diff --git a/compiler/codeGen/StgCmmPrim.hs b/compiler/codeGen/StgCmmPrim.hs
index 5c75acba5a..e4c682bf02 100644
--- a/compiler/codeGen/StgCmmPrim.hs
+++ b/compiler/codeGen/StgCmmPrim.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE CPP #-}
+
----------------------------------------------------------------------------
--
-- Stg to C--: primitive operations
@@ -767,6 +769,25 @@ emitPrimOp _ res PrefetchByteArrayOp0 args = doPrefetchByteArrayOp 0 res
emitPrimOp _ res PrefetchMutableByteArrayOp0 args = doPrefetchByteArrayOp 0 res args
emitPrimOp _ res PrefetchAddrOp0 args = doPrefetchAddrOp 0 res args
+-- Atomic read-modify-write
+emitPrimOp dflags [res] FetchAddByteArrayOp_Int [mba, ix, n] =
+ doAtomicRMW res AMO_Add mba ix (bWord dflags) n
+emitPrimOp dflags [res] FetchSubByteArrayOp_Int [mba, ix, n] =
+ doAtomicRMW res AMO_Sub mba ix (bWord dflags) n
+emitPrimOp dflags [res] FetchAndByteArrayOp_Int [mba, ix, n] =
+ doAtomicRMW res AMO_And mba ix (bWord dflags) n
+emitPrimOp dflags [res] FetchNandByteArrayOp_Int [mba, ix, n] =
+ doAtomicRMW res AMO_Nand mba ix (bWord dflags) n
+emitPrimOp dflags [res] FetchOrByteArrayOp_Int [mba, ix, n] =
+ doAtomicRMW res AMO_Or mba ix (bWord dflags) n
+emitPrimOp dflags [res] FetchXorByteArrayOp_Int [mba, ix, n] =
+ doAtomicRMW res AMO_Xor mba ix (bWord dflags) n
+emitPrimOp dflags [res] AtomicReadByteArrayOp_Int [mba, ix] =
+ doAtomicReadByteArray res mba ix (bWord dflags)
+emitPrimOp dflags [] AtomicWriteByteArrayOp_Int [mba, ix, val] =
+ doAtomicWriteByteArray mba ix (bWord dflags) val
+emitPrimOp dflags [res] CasByteArrayOp_Int [mba, ix, old, new] =
+ doCasByteArray res mba ix (bWord dflags) old new
-- The rest just translate straightforwardly
emitPrimOp dflags [res] op [arg]
@@ -1931,6 +1952,81 @@ doWriteSmallPtrArrayOp addr idx val = do
emit (setInfo addr (CmmLit (CmmLabel mkSMAP_DIRTY_infoLabel)))
------------------------------------------------------------------------------
+-- Atomic read-modify-write
+
+-- | Emit an atomic modification to a byte array element. The result
+-- reg contains that previous value of the element. Implies a full
+-- memory barrier.
+doAtomicRMW :: LocalReg -- ^ Result reg
+ -> AtomicMachOp -- ^ Atomic op (e.g. add)
+ -> CmmExpr -- ^ MutableByteArray#
+ -> CmmExpr -- ^ Index
+ -> CmmType -- ^ Type of element by which we are indexing
+ -> CmmExpr -- ^ Op argument (e.g. amount to add)
+ -> FCode ()
+doAtomicRMW res amop mba idx idx_ty n = do
+ dflags <- getDynFlags
+ let width = typeWidth idx_ty
+ addr = cmmIndexOffExpr dflags (arrWordsHdrSize dflags)
+ width mba idx
+ emitPrimCall
+ [ res ]
+ (MO_AtomicRMW width amop)
+ [ addr, n ]
+
+-- | Emit an atomic read to a byte array that acts as a memory barrier.
+doAtomicReadByteArray
+ :: LocalReg -- ^ Result reg
+ -> CmmExpr -- ^ MutableByteArray#
+ -> CmmExpr -- ^ Index
+ -> CmmType -- ^ Type of element by which we are indexing
+ -> FCode ()
+doAtomicReadByteArray res mba idx idx_ty = do
+ dflags <- getDynFlags
+ let width = typeWidth idx_ty
+ addr = cmmIndexOffExpr dflags (arrWordsHdrSize dflags)
+ width mba idx
+ emitPrimCall
+ [ res ]
+ (MO_AtomicRead width)
+ [ addr ]
+
+-- | Emit an atomic write to a byte array that acts as a memory barrier.
+doAtomicWriteByteArray
+ :: CmmExpr -- ^ MutableByteArray#
+ -> CmmExpr -- ^ Index
+ -> CmmType -- ^ Type of element by which we are indexing
+ -> CmmExpr -- ^ Value to write
+ -> FCode ()
+doAtomicWriteByteArray mba idx idx_ty val = do
+ dflags <- getDynFlags
+ let width = typeWidth idx_ty
+ addr = cmmIndexOffExpr dflags (arrWordsHdrSize dflags)
+ width mba idx
+ emitPrimCall
+ [ {- no results -} ]
+ (MO_AtomicWrite width)
+ [ addr, val ]
+
+doCasByteArray
+ :: LocalReg -- ^ Result reg
+ -> CmmExpr -- ^ MutableByteArray#
+ -> CmmExpr -- ^ Index
+ -> CmmType -- ^ Type of element by which we are indexing
+ -> CmmExpr -- ^ Old value
+ -> CmmExpr -- ^ New value
+ -> FCode ()
+doCasByteArray res mba idx idx_ty old new = do
+ dflags <- getDynFlags
+ let width = (typeWidth idx_ty)
+ addr = cmmIndexOffExpr dflags (arrWordsHdrSize dflags)
+ width mba idx
+ emitPrimCall
+ [ res ]
+ (MO_Cmpxchg width)
+ [ addr, old, new ]
+
+------------------------------------------------------------------------------
-- Helpers for emitting function calls
-- | Emit a call to @memcpy@.
diff --git a/compiler/codeGen/StgCmmProf.hs b/compiler/codeGen/StgCmmProf.hs
index f858c5a0b6..1aa08a1e58 100644
--- a/compiler/codeGen/StgCmmProf.hs
+++ b/compiler/codeGen/StgCmmProf.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE CPP #-}
+
-----------------------------------------------------------------------------
--
-- Code generation for profiling
diff --git a/compiler/codeGen/StgCmmTicky.hs b/compiler/codeGen/StgCmmTicky.hs
index b1218201a6..6913c9ec15 100644
--- a/compiler/codeGen/StgCmmTicky.hs
+++ b/compiler/codeGen/StgCmmTicky.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE BangPatterns, CPP #-}
+
-----------------------------------------------------------------------------
--
-- Code generation for ticky-ticky profiling
diff --git a/compiler/codeGen/StgCmmUtils.hs b/compiler/codeGen/StgCmmUtils.hs
index 1c6c3f2eae..bc1a15fe3c 100644
--- a/compiler/codeGen/StgCmmUtils.hs
+++ b/compiler/codeGen/StgCmmUtils.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE CPP #-}
+
-----------------------------------------------------------------------------
--
-- Code generator utilities; mostly monadic