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

Jason Dagit dagitj at gmail.com
Sun Apr 3 22:50:36 CEST 2011


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 <dagitj at gmail.com> wrote:

> ---
>  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 at .  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 at .  The returned pointer
>  -- may refer to an entirely different memory area, but will be suitably
> --
> 1.7.4.1
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/libraries/attachments/20110403/7d93f652/attachment.htm>


More information about the Libraries mailing list