Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
This module exports tools for zeroing memory. That is, filling a chunk of memory with zeros.
The exported functions behave like the ones named the same way in
base
, with the only differences being that zeroing is performed
on the allocated memory before release, and that they are generalized
to run on MonadIO
and MonadMask
for your convenience.
It is recommended to import
this module qualified
.
import qualified Memzero
Synopsis
- memzero :: forall a m. MonadIO m => Ptr a -> Int -> m ()
- memzero' :: forall a m. MonadIO m => Ptr a -> CSize -> m ()
- alloca :: forall a b m. (Storable a, MonadIO m, MonadMask m) => (Ptr a -> m b) -> m b
- allocaBytes :: forall a b m. (MonadIO m, MonadMask m) => Int -> (Ptr a -> m b) -> m b
- allocaBytesAligned :: forall a b m. (MonadIO m, MonadMask m) => Int -> Int -> (Ptr a -> m b) -> m b
- mallocForeignPtr :: forall a m. (Storable a, MonadIO m) => m (ForeignPtr a)
- mallocForeignPtrBytes :: forall a m. MonadIO m => Int -> m (ForeignPtr a)
- mallocForeignPtrAlignedBytes :: forall a m. MonadIO m => Int -> Int -> m (ForeignPtr a)
- mallocForeignPtrConc :: forall a m. (Storable a, MonadIO m) => m (ForeignPtr a)
- mallocForeignPtrConcBytes :: forall a m. MonadIO m => Int -> m (ForeignPtr a)
- mallocForeignPtrConcAlignedBytes :: forall a m. MonadIO m => Int -> Int -> m (ForeignPtr a)
- finalizerEnvFree :: FinalizerEnvPtr CSize a
- finalizerEnv :: FinalizerEnvPtr CSize a
memzero
memzero' :: forall a m. MonadIO m => Ptr a -> CSize -> m () Source #
sets memzero'
p size'size
bytes starting at p
to zero.
alloca
allocaBytes :: forall a b m. (MonadIO m, MonadMask m) => Int -> (Ptr a -> m b) -> m b Source #
behaves exactly like allocaBytes
sizebase
's allocaBytes
, but
the memory is zeroed as soon as the passed in function returns.
allocaBytesAligned :: forall a b m. (MonadIO m, MonadMask m) => Int -> Int -> (Ptr a -> m b) -> m b Source #
behaves exactly like allocaBytesAligned
size alignmentbase
's
allocaBytesAligned
, but the memory is zeroed as soon as the passed in
function returns.
mallocForeignPtr
mallocForeignPtr :: forall a m. (Storable a, MonadIO m) => m (ForeignPtr a) Source #
mallocForeignPtr
behaves exactly like base
's
mallocForeignPtr
, but the memory is zeroed
by a C finalizer before release.
C finalizers and IO
finalizers can't be mixed, so using
addForeignPtrConcFinalizer
on the obtained ForeignPtr
will fail.
You can only add C finalizers to it using addForeignPtrFinalizer
.
If you need to add IO
finalizers, use mallocForeignPtrConc
instead.
mallocForeignPtrBytes :: forall a m. MonadIO m => Int -> m (ForeignPtr a) Source #
behaves exactly like mallocForeignPtrBytes
sizebase
's
mallocForeignPtrBytes
, but the memory is zeroed
by a C finalizer before release.
C finalizers and IO
finalizers can't be mixed, so using
addForeignPtrConcFinalizer
on the obtained ForeignPtr
will fail.
You can only add C finalizers to it using addForeignPtrFinalizer
.
If you need to add IO
finalizers, use mallocForeignPtrConcBytes
instead.
mallocForeignPtrAlignedBytes :: forall a m. MonadIO m => Int -> Int -> m (ForeignPtr a) Source #
behaves exactly
like mallocForeignPtrAlignedBytes
size alignmentbase
's mallocForeignPtrAlignedBytes
, but the memory is
zeroed by a C finalizer before release.
C finalizers and IO
finalizers can't be mixed, so using
addForeignPtrConcFinalizer
on the obtained ForeignPtr
will fail.
You can only add C finalizers to it using addForeignPtrFinalizer
.
If you need to add IO
finalizers, use mallocForeignPtrConcAlignedBytes
instead.
mallocForeignPtrConc
mallocForeignPtrConc :: forall a m. (Storable a, MonadIO m) => m (ForeignPtr a) Source #
mallocForeignPtrConc
behaves exactly like base
's
mallocForeignPtr
, but the memory is zeroed
by an IO
finalizer before release.
C finalizers and IO
finalizers can't be mixed, so using
addForeignPtrFinalizer
on the obtained ForeignPtr
will fail.
You can only add IO
finalizers to it using addForeignPtrConcFinalizer
.
If you need to add C finalizers, use mallocForeignPtr
instead.
mallocForeignPtrConcBytes :: forall a m. MonadIO m => Int -> m (ForeignPtr a) Source #
behaves exactly like mallocForeignPtrConcBytes
sizebase
's
mallocForeignPtrBytes
, but the memory is zeroed
by an IO
finalizer before release.
C finalizers and IO
finalizers can't be mixed, so using
addForeignPtrFinalizer
on the obtained ForeignPtr
will fail.
You can only add IO
finalizers to it using addForeignPtrConcFinalizer
.
If you need to add C finalizers, use mallocForeignPtrBytes
instead.
mallocForeignPtrConcAlignedBytes :: forall a m. MonadIO m => Int -> Int -> m (ForeignPtr a) Source #
behaves exactly
like mallocForeignPtrConcAlignedBytes
size alignmentbase
's mallocForeignPtrAlignedBytes
, but the memory is
zeroed by an IO
finalizer before release.
C finalizers and IO
finalizers can't be mixed, so using
addForeignPtrFinalizer
on the obtained ForeignPtr
will fail.
You can only add IO
finalizers to it using addForeignPtrConcFinalizer
.
If you need to add C finalizers, use mallocForeignPtrAlignedBytes
instead.
C finalizers
finalizerEnv :: FinalizerEnvPtr CSize a Source #
This FinalizerEnvPtr
zeroes CSize
bytes starting at
.Ptr
a
Contrary to finalizerEnvFree
, this doesn't free
the
.Ptr
CSize
C support
This library also offers some tools that can be used from the C language.
To have access to them, you have to #include
the <hs_memzero.h>
header
that is installed together with this Haskell memzero
library. If you are
using Cabal, then this header file will be readily available for you to
#include
without having to do anything special.
#include <hs_memzero.h>
The following C functions are exported:
/* This is the C version ofmemzero'
*/ void hs_memzero(void * p, size_t size) /* This is the C version offinalizerEnvFree
*/ void hs_memzero_finalizerEnvFree(size_t * size, void * p) /* This is the C version offinalizerEnv
*/ void hs_memzero_finalizerEnv(size_t * size, void * p)