Skip to content

Commit

Permalink
Add 'fillBytes' to Foreign.Marshal.Utils.
Browse files Browse the repository at this point in the history
fillBytes uses 'memset' to fill a memory area with a given byte value.

Reviewed By: austin, hvr

Differential Revision: https://phabricator.haskell.org/D465
  • Loading branch information
ifesdjeen authored and hvr committed Nov 21, 2014
1 parent c0ad5bc commit 3583312
Show file tree
Hide file tree
Showing 2 changed files with 19 additions and 2 deletions.
19 changes: 17 additions & 2 deletions libraries/base/Foreign/Marshal/Utils.hs
Expand Up @@ -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
Expand Down Expand Up @@ -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
-- -------------------
Expand All @@ -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)
2 changes: 2 additions & 0 deletions libraries/base/changelog.md
Expand Up @@ -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
Expand Down

0 comments on commit 3583312

Please sign in to comment.