[commit: packages/primitive] ghc-head: Add setAddr (bfbae1a)

git at git.haskell.org git at git.haskell.org
Thu Sep 26 11:44:42 CEST 2013


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

On branch  : ghc-head
Link       : http://git.haskell.org/packages/primitive.git/commitdiff/bfbae1afd5421788b2316aa3dd1f864c1e6ff4e0

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

commit bfbae1afd5421788b2316aa3dd1f864c1e6ff4e0
Author: Roman Leshchinskiy <rl at cse.unsw.edu.au>
Date:   Thu Jan 26 16:03:27 2012 -0700

    Add setAddr


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

bfbae1afd5421788b2316aa3dd1f864c1e6ff4e0
 Data/Primitive/Addr.hs |   17 ++++++++++++++++-
 1 file changed, 16 insertions(+), 1 deletion(-)

diff --git a/Data/Primitive/Addr.hs b/Data/Primitive/Addr.hs
index fb0fd84..a38cfd2 100644
--- a/Data/Primitive/Addr.hs
+++ b/Data/Primitive/Addr.hs
@@ -12,11 +12,20 @@
 --
 
 module Data.Primitive.Addr (
+  -- * Types
   Addr(..),
 
+  -- * Address arithmetic
   nullAddr, plusAddr, minusAddr, remAddr,
+
+  -- * Element access
   indexOffAddr, readOffAddr, writeOffAddr,
-  copyAddr, moveAddr, memcpyAddr
+
+  -- * Block operations
+  copyAddr, moveAddr, setAddr,
+
+  -- * Deprecated operations
+  memcpyAddr
 ) where
 
 import Control.Monad.Primitive
@@ -88,6 +97,12 @@ moveAddr :: PrimMonad m => Addr         -- ^ destination address
 moveAddr (Addr dst#) (Addr src#) n
   = unsafePrimToPrim $ moveBytes (Ptr dst#) (Ptr src#) n
 
+-- | Fill a memory block of with the given value. The length is in
+-- elements of type @a@ rather than in bytes.
+setAddr :: (Prim a, PrimMonad m) => Addr -> Int -> a -> m ()
+{-# INLINE setAddr #-}
+setAddr (Addr addr#) (I# n#) x = primitive_ (setOffAddr# addr# 0# n# x)
+
 memcpyAddr :: PrimMonad m => Addr -> Addr -> Int -> m ()
 {-# INLINE memcpyAddr #-}
 {-# DEPRECATED memcpyAddr "Use copyAddr instead" #-}




More information about the ghc-commits mailing list