[Git][ghc/ghc][wip/ioref-swap-xchg] compiler: Implement atomicSwapIORef with xchg
Ben Gamari (@bgamari)
gitlab at gitlab.haskell.org
Fri Mar 24 04:15:18 UTC 2023
Ben Gamari pushed to branch wip/ioref-swap-xchg at Glasgow Haskell Compiler / GHC
Commits:
873cfa51 by Ben Gamari at 2023-03-24T00:15:11-04:00
compiler: Implement atomicSwapIORef with xchg
- - - - -
8 changed files:
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/StgToCmm/Prim.hs
- compiler/GHC/StgToJS/Prim.hs
- libraries/base/GHC/IORef.hs
- rts/PrimOps.cmm
- rts/RtsSymbols.c
- rts/include/Cmm.h
- rts/include/stg/MiscClosures.h
Changes:
=====================================
compiler/GHC/Builtin/primops.txt.pp
=====================================
@@ -2513,6 +2513,13 @@ primop WriteMutVarOp "writeMutVar#" GenPrimOp
has_side_effects = True
code_size = { primOpCodeSizeForeignCall } -- for the write barrier
+primop AtomicSwapMutVarOp "atomicSwapMutVar#" GenPrimOp
+ MutVar# s v -> v -> State# s -> (# State# s, v #)
+ {Atomically exchange the value of a 'MutVar#'.}
+ with
+ out_of_line = True
+ has_side_effects = True
+
-- Note [Why not an unboxed tuple in atomicModifyMutVar2#?]
-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-- Looking at the type of atomicModifyMutVar2#, one might wonder why
=====================================
compiler/GHC/StgToCmm/Prim.hs
=====================================
@@ -1559,6 +1559,7 @@ emitPrimOp cfg primop =
ResizeMutableByteArrayOp_Char -> alwaysExternal
ShrinkSmallMutableArrayOp_Char -> alwaysExternal
NewMutVarOp -> alwaysExternal
+ AtomicSwapMutVarOp -> alwaysExternal
AtomicModifyMutVar2Op -> alwaysExternal
AtomicModifyMutVar_Op -> alwaysExternal
CasMutVarOp -> alwaysExternal
=====================================
compiler/GHC/StgToJS/Prim.hs
=====================================
@@ -859,6 +859,8 @@ genPrim prof bound ty op = case op of
AtomicModifyMutVar2Op -> \[r1,r2] [m,f] -> PrimInline $ appT [r1,r2] "h$atomicModifyMutVar2" [m,f]
AtomicModifyMutVar_Op -> \[r1,r2] [m,f] -> PrimInline $ appT [r1,r2] "h$atomicModifyMutVar" [m,f]
+ AtomicSwapMutVarOp -> \[r] [mv,v] -> PrimInline $ mconcat
+ [ r |= mv .^ "val", mv .^ "val" |= v ]
CasMutVarOp -> \[status,r] [mv,o,n] -> PrimInline $ ifS (mv .^ "val" .===. o)
(mconcat [status |= zero_, r |= n, mv .^ "val" |= n])
(mconcat [status |= one_ , r |= mv .^ "val"])
=====================================
libraries/base/GHC/IORef.hs
=====================================
@@ -127,12 +127,9 @@ atomicModifyIORef'_ ref f = do
-- | Atomically replace the contents of an 'IORef', returning
-- the old contents.
atomicSwapIORef :: IORef a -> a -> IO a
--- Bad implementation! This will be a primop shortly.
atomicSwapIORef (IORef (STRef ref)) new = IO $ \s ->
- case atomicModifyMutVar2# ref (\_old -> Box new) s of
- (# s', old, Box _new #) -> (# s', old #)
-
-data Box a = Box a
+ case atomicSwapMutVar# ref new s of
+ (# s', old #) -> (# s', old #)
-- | Strict version of 'Data.IORef.atomicModifyIORef'. This forces both
-- the value stored in the 'IORef' and the value returned. The new value
=====================================
rts/PrimOps.cmm
=====================================
@@ -689,6 +689,17 @@ stg_newMutVarzh ( gcptr init )
return (mv);
}
+stg_atomicSwapMutVarzh ( gcptr mv, gcptr new )
+ /* MutVar# s a -> a -> State# s -> (# State#, a #) */
+{
+ W_ old;
+ (old) = prim %xchgW(mv + SIZEOF_StgHeader + OFFSET_StgMutVar_var, new);
+ if (GET_INFO(mv) == stg_MUT_VAR_CLEAN_info) {
+ ccall dirty_MUT_VAR(BaseReg "ptr", mv "ptr", old "ptr");
+ }
+ return (old);
+}
+
// RRN: To support the "ticketed" approach, we return the NEW rather
// than old value if the CAS is successful. This is received in an
// opaque form in the Haskell code, preventing the compiler from
=====================================
rts/RtsSymbols.c
=====================================
@@ -633,6 +633,7 @@ extern char **environ;
SymI_HasDataProto(stg_writeIOPortzh) \
SymI_HasDataProto(stg_newIOPortzh) \
SymI_HasDataProto(stg_noDuplicatezh) \
+ SymI_HasDataProto(stg_atomicSwapMutVarzh) \
SymI_HasDataProto(stg_atomicModifyMutVar2zh) \
SymI_HasDataProto(stg_atomicModifyMutVarzuzh) \
SymI_HasDataProto(stg_casMutVarzh) \
=====================================
rts/include/Cmm.h
=====================================
@@ -193,8 +193,10 @@
#if SIZEOF_W == 4
#define cmpxchgW cmpxchg32
+#define xchgW xchg32
#elif SIZEOF_W == 8
#define cmpxchgW cmpxchg64
+#define xchgW xchg64
#endif
/* -----------------------------------------------------------------------------
=====================================
rts/include/stg/MiscClosures.h
=====================================
@@ -481,6 +481,7 @@ RTS_FUN_DECL(stg_copySmallMutableArrayzh);
RTS_FUN_DECL(stg_casSmallArrayzh);
RTS_FUN_DECL(stg_newMutVarzh);
+RTS_FUN_DECL(stg_atomicSwapMutVarzh);
RTS_FUN_DECL(stg_atomicModifyMutVar2zh);
RTS_FUN_DECL(stg_atomicModifyMutVarzuzh);
RTS_FUN_DECL(stg_casMutVarzh);
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/873cfa51f3b49dfc8c4923456c10c7eb9d3cfef2
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/873cfa51f3b49dfc8c4923456c10c7eb9d3cfef2
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20230324/1ba2e3e7/attachment-0001.html>
More information about the ghc-commits
mailing list