[PATCH 1/2] add calloc and callocBytes to Foreign.Marshal.Alloc

--- Foreign/Marshal/Alloc.hs | 29 +++++++++++++++++++++++++++++ 1 files changed, 29 insertions(+), 0 deletions(-) diff --git a/Foreign/Marshal/Alloc.hs b/Foreign/Marshal/Alloc.hs index 612d2c7..148190b 100644 --- a/Foreign/Marshal/Alloc.hs +++ b/Foreign/Marshal/Alloc.hs @@ -53,6 +53,9 @@ module Foreign.Marshal.Alloc ( malloc, -- :: Storable a => IO (Ptr a) mallocBytes, -- :: Int -> IO (Ptr a) + calloc, -- :: Storable a => IO (Ptr a) + callocBytes, -- :: Int -> IO (Ptr a) + realloc, -- :: Storable b => Ptr a -> IO (Ptr b) reallocBytes, -- :: Ptr a -> Int -> IO (Ptr a) @@ -168,6 +171,32 @@ allocaBytesAligned :: Int -> Int -> (Ptr a -> IO b) -> IO b allocaBytesAligned size align = allocaBytes size -- wrong #endif +-- | Allocate a block of memory that is sufficient to hold values of type +-- @a@. The size of the area allocated is determined by the 'sizeOf' +-- method from the instance of 'Storable' for the appropriate type. +-- The memory is initalized to 0. +-- +-- The memory may be deallocated using 'free' or 'finalizerFree' when +-- no longer required. +-- +{-# 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 tyes that fit into a memory block of the allocated size. +-- The memory is initialized to 0. +-- +-- The memory may be deallocated using 'free' or 'finalizerFree' when +-- no longer required. +-- +callocBytes :: Int -> IO (Ptr a) +callocBytes size = failWhenNULL "calloc" (_calloc (fromIntegral size) 1) + -- |Resize a memory area that was allocated with 'malloc' or 'mallocBytes' -- to the size needed to store values of type @b@. The returned pointer -- may refer to an entirely different memory area, but will be suitably -- 1.7.4.1

--- Foreign/Marshal/Utils.hs | 26 ++++++++++++++++++++++++-- 1 files changed, 24 insertions(+), 2 deletions(-) diff --git a/Foreign/Marshal/Utils.hs b/Foreign/Marshal/Utils.hs index bf9bdb3..2413e73 100644 --- a/Foreign/Marshal/Utils.hs +++ b/Foreign/Marshal/Utils.hs @@ -43,8 +43,11 @@ module Foreign.Marshal.Utils ( -- ** Haskellish interface to memcpy and memmove -- | (argument order: destination, source) -- - copyBytes, -- :: Ptr a -> Ptr a -> Int -> IO () - moveBytes, -- :: Ptr a -> Ptr a -> Int -> IO () + copy, -- :: Storable a => Ptr a -> Ptr a -> IO () + copyBytes, -- :: Ptr a -> Ptr a -> Int -> IO () + + move, -- :: Storable a => Ptr a -> Ptr a -> IO () + moveBytes, -- :: Ptr a -> Ptr a -> Int -> IO () ) where import Data.Maybe @@ -169,6 +172,25 @@ moveBytes :: Ptr a -> Ptr a -> Int -> IO () moveBytes dest src size = do _ <- memmove dest src (fromIntegral size) return () +-- |Uses 'sizeOf' to copy bytes from the second area (source) into the +-- first (destination); the copied areas may /not/ overlap +-- +{-# INLINE copy #-} +copy :: Storable a => Ptr a -> Ptr a -> IO () +copy dest src = copyBytes dest src (sizeOf (type_ src)) + where + type_ :: Ptr a -> a + type_ = undefined + +-- |Uses 'sizeOf' to copy bytes from the second area (source) into the +-- first (destination); the copied areas /may/ overlap +-- +{-# INLINE move #-} +move :: Storable a => Ptr a -> Ptr a -> IO () +move dest src = moveBytes dest src (sizeOf (type_ src)) + where + type_ :: Ptr a -> a + type_ = undefined -- auxilliary routines -- ------------------- -- 1.7.4.1

Someone should double check this patch (and my other email).
I tested them by creating this package:
http://hackage.haskell.org/package/missing-foreign
I put that on hackage in case a) these are not accepted to base, or b)
someone is using a version of base that doesn't have them yet.
Thanks,
Jason
On Sun, Apr 3, 2011 at 1:28 PM, Jason Dagit
--- Foreign/Marshal/Alloc.hs | 29 +++++++++++++++++++++++++++++ 1 files changed, 29 insertions(+), 0 deletions(-)
diff --git a/Foreign/Marshal/Alloc.hs b/Foreign/Marshal/Alloc.hs index 612d2c7..148190b 100644 --- a/Foreign/Marshal/Alloc.hs +++ b/Foreign/Marshal/Alloc.hs @@ -53,6 +53,9 @@ module Foreign.Marshal.Alloc ( malloc, -- :: Storable a => IO (Ptr a) mallocBytes, -- :: Int -> IO (Ptr a)
+ calloc, -- :: Storable a => IO (Ptr a) + callocBytes, -- :: Int -> IO (Ptr a) + realloc, -- :: Storable b => Ptr a -> IO (Ptr b) reallocBytes, -- :: Ptr a -> Int -> IO (Ptr a)
@@ -168,6 +171,32 @@ allocaBytesAligned :: Int -> Int -> (Ptr a -> IO b) -> IO b allocaBytesAligned size align = allocaBytes size -- wrong #endif
+-- | Allocate a block of memory that is sufficient to hold values of type +-- @a@. The size of the area allocated is determined by the 'sizeOf' +-- method from the instance of 'Storable' for the appropriate type. +-- The memory is initalized to 0. +-- +-- The memory may be deallocated using 'free' or 'finalizerFree' when +-- no longer required. +-- +{-# 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 tyes that fit into a memory block of the allocated size. +-- The memory is initialized to 0. +-- +-- The memory may be deallocated using 'free' or 'finalizerFree' when +-- no longer required. +-- +callocBytes :: Int -> IO (Ptr a) +callocBytes size = failWhenNULL "calloc" (_calloc (fromIntegral size) 1) + -- |Resize a memory area that was allocated with 'malloc' or 'mallocBytes' -- to the size needed to store values of type @b@. The returned pointer -- may refer to an entirely different memory area, but will be suitably -- 1.7.4.1

Hi Jason, On Sun, Apr 03, 2011 at 01:28:13PM -0700, Jason Dagit wrote:
[PATCH 1/2] add calloc and callocBytes to Foreign.Marshal.Alloc
The procedure for proposing a change to the core library APIs is described here: http://www.haskell.org/haskellwiki/Library_submissions Thanks Ian

On Fri, Apr 22, 2011 at 5:44 AM, Ian Lynagh
Hi Jason,
On Sun, Apr 03, 2011 at 01:28:13PM -0700, Jason Dagit wrote:
[PATCH 1/2] add calloc and callocBytes to Foreign.Marshal.Alloc
The procedure for proposing a change to the core library APIs is described here: http://www.haskell.org/haskellwiki/Library_submissions
Thanks. I admit I did not read that before sending these patches but now I need further clarification. It says to send a patch and I did that. I made the changes against the latest version of base (well, it was the latest version when I sent the patch almost 3 weeks ago). It's very hard for me to test portability. I don't have hugs on any machines. The most I could do there is test on a few OSs with ghc. I've done my best to follow the style and create documentation. As for testing, I put them on hackage where I've used them in at least one package successfully. My rationale is simple. Sometimes you need calloc instead of malloc and there was no existing binding so I created one. It seems like it should live in base. That wiki page doesn't say how long the discussion period should be or give advice on how to determine the size. What would you recommend for this patch? So it sounds like the things I missed were: * putting "Proposal:" in the subject line * setting a discussion period * attaching my patch to the trac instance (can I send a pull request on github instead?) In summary, I need clarification on: * Can I send a pull request or do I need to continue using git's patch sending commands? * How long of a discussion window do I set? Thanks, Jason

On Fri, Apr 22, 2011 at 07:20:55AM -0700, Jason Dagit wrote:
That wiki page doesn't say how long the discussion period should be or give advice on how to determine the size. What would you recommend for this patch?
I just updated the page to recommend 2 weeks, which I think is the status quo.
So it sounds like the things I missed were: * putting "Proposal:" in the subject line * setting a discussion period * attaching my patch to the trac instance (can I send a pull request on github instead?)
You don't need to make a trac ticket for it until the proposal has been accepted. Anything that means we see that the patch needs to be applied is OK. Currently pull requests don't get sent to the mailing list though, and there doesn't seem to be an easy way to set that up. I also didn't notice a rationale for the change. The type signatures looked the same as for the malloc functions, so I don't know what the difference is. Thanks Ian

On Fri, Apr 22, 2011 at 8:59 AM, Ian Lynagh
On Fri, Apr 22, 2011 at 07:20:55AM -0700, Jason Dagit wrote:
That wiki page doesn't say how long the discussion period should be or
give
advice on how to determine the size. What would you recommend for this patch?
I just updated the page to recommend 2 weeks, which I think is the status quo.
So it sounds like the things I missed were: * putting "Proposal:" in the subject line * setting a discussion period * attaching my patch to the trac instance (can I send a pull request on github instead?)
You don't need to make a trac ticket for it until the proposal has been accepted.
Right, I did understand that.
Anything that means we see that the patch needs to be applied is OK. Currently pull requests don't get sent to the mailing list though, and there doesn't seem to be an easy way to set that up.
Good to know.
I also didn't notice a rationale for the change. The type signatures looked the same as for the malloc functions, so I don't know what the difference is.
The difference is that calloc will initialize the allocated memory to zeros. Some C libraries assume this, at least freetype2 does, and since I want to use that library from Haskell I needed a binding to calloc. I assume others will run into this need eventually as well. When I send a "proposal:..." email, hopefully this weekend, I'll definitely make the rationale clear. Thanks, Jason

calloc is just a multiplication followed by malloc followed by memset. Is it
really worth creating a new binding for that? It always seemed like a bit of
a silly API to me to begin with.
On Fri, Apr 22, 2011 at 12:08 PM, Jason Dagit
On Fri, Apr 22, 2011 at 8:59 AM, Ian Lynagh
wrote: On Fri, Apr 22, 2011 at 07:20:55AM -0700, Jason Dagit wrote:
That wiki page doesn't say how long the discussion period should be or
give
advice on how to determine the size. What would you recommend for this patch?
I just updated the page to recommend 2 weeks, which I think is the status quo.
So it sounds like the things I missed were: * putting "Proposal:" in the subject line * setting a discussion period * attaching my patch to the trac instance (can I send a pull request on github instead?)
You don't need to make a trac ticket for it until the proposal has been accepted.
Right, I did understand that.
Anything that means we see that the patch needs to be applied is OK. Currently pull requests don't get sent to the mailing list though, and there doesn't seem to be an easy way to set that up.
Good to know.
I also didn't notice a rationale for the change. The type signatures looked the same as for the malloc functions, so I don't know what the difference is.
The difference is that calloc will initialize the allocated memory to zeros. Some C libraries assume this, at least freetype2 does, and since I want to use that library from Haskell I needed a binding to calloc. I assume others will run into this need eventually as well. When I send a "proposal:..." email, hopefully this weekend, I'll definitely make the rationale clear.
Thanks, Jason
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Fri, Apr 22, 2011 at 12:05 PM, Daniel Peebles
calloc is just a multiplication followed by malloc followed by memset. Is it really worth creating a new binding for that? It always seemed like a bit of a silly API to me to begin with.
It doesn't have to be a binding. If you'd prefer to provide a Haskell implementation in terms of malloc/copyBytes that sounds fine too. I wasn't sure how to best do that so a binding seemed the most straightforward. Note that in my binding, I gave it the same type as malloc, which is to say it is always in terms of bytes. The actual calloc api seems more like what we call mallocArray and I didn't personally need that functionality so I went for something that matched malloc. I'm flexible on that point. Jason
On Fri, Apr 22, 2011 at 12:08 PM, Jason Dagit
wrote: On Fri, Apr 22, 2011 at 8:59 AM, Ian Lynagh
wrote: On Fri, Apr 22, 2011 at 07:20:55AM -0700, Jason Dagit wrote:
That wiki page doesn't say how long the discussion period should be or
give
advice on how to determine the size. What would you recommend for this patch?
I just updated the page to recommend 2 weeks, which I think is the status quo.
So it sounds like the things I missed were: * putting "Proposal:" in the subject line * setting a discussion period * attaching my patch to the trac instance (can I send a pull request on github instead?)
You don't need to make a trac ticket for it until the proposal has been accepted.
Right, I did understand that.
Anything that means we see that the patch needs to be applied is OK. Currently pull requests don't get sent to the mailing list though, and there doesn't seem to be an easy way to set that up.
Good to know.
I also didn't notice a rationale for the change. The type signatures looked the same as for the malloc functions, so I don't know what the difference is.
The difference is that calloc will initialize the allocated memory to zeros. Some C libraries assume this, at least freetype2 does, and since I want to use that library from Haskell I needed a binding to calloc. I assume others will run into this need eventually as well. When I send a "proposal:..." email, hopefully this weekend, I'll definitely make the rationale clear.
Thanks, Jason
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Fri, Apr 22, 2011 at 1:17 PM, Jason Dagit
It doesn't have to be a binding. If you'd prefer to provide a Haskell
implementation in terms of malloc/copyBytes that sounds fine too. I wasn't sure how to best do that so a binding seemed the most straightforward.
I was looking at this after I sent the email. copyBytes and moveBytes are bindings to memcpy and memmove, not memset. I don't see a binding to memset in Foreign. Perhaps that should be added as well. Jason

NB: libc can usually lean on the knowledge that virtual memory retrieved
from sbrk is already initialized to 0 when you calloc for memory initialized
to 0, so it can be vastly more efficient than malloc + memset and it can
decrease the number of useless 0 pages floating around.
http://stackoverflow.com/questions/2688466/why-mallocmemset-slower-than-call...
http://stackoverflow.com/questions/2688466/why-mallocmemset-slower-than-call...
-Edward
On Fri, Apr 22, 2011 at 3:05 PM, Daniel Peebles
calloc is just a multiplication followed by malloc followed by memset. Is it really worth creating a new binding for that? It always seemed like a bit of a silly API to me to begin with.
On Fri, Apr 22, 2011 at 12:08 PM, Jason Dagit
wrote: On Fri, Apr 22, 2011 at 8:59 AM, Ian Lynagh
wrote: On Fri, Apr 22, 2011 at 07:20:55AM -0700, Jason Dagit wrote:
That wiki page doesn't say how long the discussion period should be or
give
advice on how to determine the size. What would you recommend for this patch?
I just updated the page to recommend 2 weeks, which I think is the status quo.
So it sounds like the things I missed were: * putting "Proposal:" in the subject line * setting a discussion period * attaching my patch to the trac instance (can I send a pull request on github instead?)
You don't need to make a trac ticket for it until the proposal has been accepted.
Right, I did understand that.
Anything that means we see that the patch needs to be applied is OK. Currently pull requests don't get sent to the mailing list though, and there doesn't seem to be an easy way to set that up.
Good to know.
I also didn't notice a rationale for the change. The type signatures looked the same as for the malloc functions, so I don't know what the difference is.
The difference is that calloc will initialize the allocated memory to zeros. Some C libraries assume this, at least freetype2 does, and since I want to use that library from Haskell I needed a binding to calloc. I assume others will run into this need eventually as well. When I send a "proposal:..." email, hopefully this weekend, I'll definitely make the rationale clear.
Thanks, Jason
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
participants (5)
-
Daniel Peebles
-
Edward Kmett
-
Ian Lynagh
-
Jason Dagit
-
Matthias Kilian