[commit: ghc] master: Add 'fillBytes' to Foreign.Marshal.Utils. (3583312)

git at git.haskell.org git at git.haskell.org
Fri Nov 21 19:50:33 UTC 2014


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

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

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

commit 35833122da8ddb2c0e7aaee0c9b6089af52e38b1
Author: Alex Petrov <alexp at coffeenco.de>
Date:   Fri Nov 21 19:24:37 2014 +0100

    Add 'fillBytes' to Foreign.Marshal.Utils.
    
    fillBytes uses 'memset' to fill a memory area with a given byte value.
    
    Reviewed By: austin, hvr
    
    Differential Revision: https://phabricator.haskell.org/D465


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

35833122da8ddb2c0e7aaee0c9b6089af52e38b1
 libraries/base/Foreign/Marshal/Utils.hs | 19 +++++++++++++++++--
 libraries/base/changelog.md             |  2 ++
 2 files changed, 19 insertions(+), 2 deletions(-)

diff --git a/libraries/base/Foreign/Marshal/Utils.hs b/libraries/base/Foreign/Marshal/Utils.hs
index 4654e55..c24c249 100644
--- a/libraries/base/Foreign/Marshal/Utils.hs
+++ b/libraries/base/Foreign/Marshal/Utils.hs
@@ -43,13 +43,18 @@ module Foreign.Marshal.Utils (
   --
   copyBytes,
   moveBytes,
+
+  -- ** Filling up memory area with required values
+  --
+  fillBytes,
 ) where
 
 import Data.Maybe
 import Foreign.Ptr              ( Ptr, nullPtr )
 import Foreign.Storable         ( Storable(poke) )
-import Foreign.C.Types          ( CSize(..) )
+import Foreign.C.Types          ( CSize(..), CInt(..) )
 import Foreign.Marshal.Alloc    ( malloc, alloca )
+import Data.Word                ( Word8 )
 
 import GHC.Real                 ( fromIntegral )
 import GHC.Num
@@ -161,6 +166,16 @@ moveBytes               :: Ptr a -> Ptr a -> Int -> IO ()
 moveBytes dest src size  = do _ <- memmove dest src (fromIntegral size)
                               return ()
 
+-- Filling up memory area with required values
+-- -------------------------------------------
+
+-- |Fill a given number of bytes in memory area with a byte value.
+--
+-- /Since: 4.8.0.0/
+fillBytes               :: Ptr a -> Word8 -> Int -> IO ()
+fillBytes dest char size = do
+  _ <- memset dest (fromIntegral char) (fromIntegral size)
+  return ()
 
 -- auxilliary routines
 -- -------------------
@@ -169,4 +184,4 @@ moveBytes dest src size  = do _ <- memmove dest src (fromIntegral size)
 --
 foreign import ccall unsafe "string.h" memcpy  :: Ptr a -> Ptr a -> CSize -> IO (Ptr a)
 foreign import ccall unsafe "string.h" memmove :: Ptr a -> Ptr a -> CSize -> IO (Ptr a)
-
+foreign import ccall unsafe "string.h" memset  :: Ptr a -> CInt  -> CSize -> IO (Ptr a)
diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md
index 7825c97..3e110a7 100644
--- a/libraries/base/changelog.md
+++ b/libraries/base/changelog.md
@@ -102,6 +102,8 @@
   * Add `scanl'`, a strictly accumulating version of `scanl`, to `Data.List`
     and `Data.OldList`. (#9368)
 
+  * Add `fillBytes` to `Foreign.Marshal.Utils`.
+
 ## 4.7.0.1  *Jul 2014*
 
   * Bundled with GHC 7.8.3



More information about the ghc-commits mailing list