[commit: ghc] master: Implement `calloc{, Bytes, Array, Array0}` allocators (08610c1)
git at git.haskell.org
git at git.haskell.org
Sat Dec 6 00:35:52 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/08610c1fdc7816c74faed40f8a7d3c4b4758709e/ghc
>---------------------------------------------------------------
commit 08610c1fdc7816c74faed40f8a7d3c4b4758709e
Author: Alex Petrov <alexp at coffeenco.de>
Date: Fri Dec 5 14:56:14 2014 -0600
Implement `calloc{,Bytes,Array,Array0}` allocators
Summary:
This adds zero-initialising versions of `malloc{,Bytes,Array,Array0}`
* Add `calloc` and `callocBytes` to `Foreign.Marshal.Alloc`.
* Add `callocArray` and `callocArray0` to `Foreign.Marshal.Array`.
Reviewers: ekmett, duncan, austin, hvr
Reviewed By: austin, hvr
Subscribers: ezyang, simonmar, ekmett, duncan, thomie, carter
Projects: #ghc
Differential Revision: https://phabricator.haskell.org/D527
GHC Trac Issues: #9859
>---------------------------------------------------------------
08610c1fdc7816c74faed40f8a7d3c4b4758709e
libraries/base/Foreign/Marshal/Alloc.hs | 18 ++++++++++++++++++
libraries/base/Foreign/Marshal/Array.hs | 19 ++++++++++++++++++-
libraries/base/changelog.md | 4 ++++
3 files changed, 40 insertions(+), 1 deletion(-)
diff --git a/libraries/base/Foreign/Marshal/Alloc.hs b/libraries/base/Foreign/Marshal/Alloc.hs
index d43589f..264c10c 100644
--- a/libraries/base/Foreign/Marshal/Alloc.hs
+++ b/libraries/base/Foreign/Marshal/Alloc.hs
@@ -49,6 +49,9 @@ module Foreign.Marshal.Alloc (
malloc,
mallocBytes,
+ calloc,
+ callocBytes,
+
realloc,
reallocBytes,
@@ -82,6 +85,15 @@ malloc = doMalloc undefined
doMalloc :: Storable b => b -> IO (Ptr b)
doMalloc dummy = mallocBytes (sizeOf dummy)
+-- |Like 'malloc' but memory is filled with bytes of value zero.
+--
+{-# INLINE calloc #-}
+calloc :: Storable a => IO (Ptr a)
+calloc = doCalloc undefined
+ where
+ doCalloc :: Storable b => b -> IO (Ptr b)
+ doCalloc dummy = callocBytes (sizeOf dummy)
+
-- |Allocate a block of memory of the given number of bytes.
-- The block of memory is sufficiently aligned for any of the basic
-- foreign types that fits into a memory block of the allocated size.
@@ -92,6 +104,11 @@ malloc = doMalloc undefined
mallocBytes :: Int -> IO (Ptr a)
mallocBytes size = failWhenNULL "malloc" (_malloc (fromIntegral size))
+-- |Llike 'mallocBytes' but memory is filled with bytes of value zero.
+--
+callocBytes :: Int -> IO (Ptr a)
+callocBytes size = failWhenNULL "calloc" $ _calloc 1 (fromIntegral size)
+
-- |@'alloca' f@ executes the computation @f@, passing as argument
-- a pointer to a temporarily allocated block of memory sufficient to
-- hold values of type @a at .
@@ -198,6 +215,7 @@ failWhenNULL name f = do
-- basic C routines needed for memory allocation
--
foreign import ccall unsafe "stdlib.h malloc" _malloc :: CSize -> IO (Ptr a)
+foreign import ccall unsafe "stdlib.h calloc" _calloc :: CSize -> CSize -> IO (Ptr a)
foreign import ccall unsafe "stdlib.h realloc" _realloc :: Ptr a -> CSize -> IO (Ptr b)
foreign import ccall unsafe "stdlib.h free" _free :: Ptr a -> IO ()
diff --git a/libraries/base/Foreign/Marshal/Array.hs b/libraries/base/Foreign/Marshal/Array.hs
index 8d7dcfb..0aea67b 100644
--- a/libraries/base/Foreign/Marshal/Array.hs
+++ b/libraries/base/Foreign/Marshal/Array.hs
@@ -30,6 +30,9 @@ module Foreign.Marshal.Array (
reallocArray,
reallocArray0,
+ callocArray,
+ callocArray0,
+
-- ** Marshalling
--
peekArray,
@@ -66,7 +69,7 @@ module Foreign.Marshal.Array (
import Foreign.Ptr (Ptr, plusPtr)
import Foreign.Storable (Storable(alignment,sizeOf,peekElemOff,pokeElemOff))
-import Foreign.Marshal.Alloc (mallocBytes, allocaBytesAligned, reallocBytes)
+import Foreign.Marshal.Alloc (mallocBytes, callocBytes, allocaBytesAligned, reallocBytes)
import Foreign.Marshal.Utils (copyBytes, moveBytes)
import GHC.Num
@@ -91,6 +94,20 @@ mallocArray = doMalloc undefined
mallocArray0 :: Storable a => Int -> IO (Ptr a)
mallocArray0 size = mallocArray (size + 1)
+-- |Like 'mallocArray', but allocated memory is filled with bytes of value zero.
+--
+callocArray :: Storable a => Int -> IO (Ptr a)
+callocArray = doCalloc undefined
+ where
+ doCalloc :: Storable a' => a' -> Int -> IO (Ptr a')
+ doCalloc dummy size = callocBytes (size * sizeOf dummy)
+
+-- |Like 'callocArray0', but allocated memory is filled with bytes of value
+-- zero.
+--
+callocArray0 :: Storable a => Int -> IO (Ptr a)
+callocArray0 size = callocArray (size + 1)
+
-- |Temporarily allocate space for the given number of elements
-- (like 'Foreign.Marshal.Alloc.alloca', but for multiple elements).
--
diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md
index ef3e9ae..3b06dba 100644
--- a/libraries/base/changelog.md
+++ b/libraries/base/changelog.md
@@ -130,6 +130,10 @@
* Make `read . show = id` for `Data.Fixed` (#9240)
+ * Add `calloc` and `callocBytes` to `Foreign.Marshal.Alloc`.
+
+ * Add `callocArray` and `callocArray0` to `Foreign.Marshal.Array`.
+
## 4.7.0.2 *Dec 2014*
* Bundled with GHC 7.8.4
More information about the ghc-commits
mailing list