Safe Haskell | None |
---|---|
Language | Haskell2010 |
A collection of data types, classes, and functions for interfacing
with another programming language using the Prim
interface instead
of the Storable
interface.
Synopsis
- sizeOf :: Prim a => a -> Int
- alignment :: Prim a => a -> Int
- peek :: forall a. Prim a => Ptr a -> IO a
- peekElemOff :: forall a. Prim a => Ptr a -> Int -> IO a
- peekByteOff :: forall a. Prim a => Ptr Void -> Int -> IO a
- poke :: forall a. Prim a => Ptr a -> a -> IO ()
- pokeElemOff :: forall a. Prim a => Ptr a -> Int -> a -> IO ()
- pokeByteOff :: forall a. Prim a => Ptr Void -> Int -> a -> IO ()
- alloca :: forall a b. Prim a => (Ptr a -> IO b) -> IO b
- allocaBytes :: Int -> (Ptr a -> IO b) -> IO b
- allocaBytesAligned :: Int -> Int -> (Ptr a -> IO b) -> IO b
- malloc :: forall a. Prim a => IO (Ptr a)
- mallocBytes :: Int -> IO (Ptr a)
- calloc :: forall a. Prim a => IO (Ptr a)
- callocBytes :: Int -> IO (Ptr a)
- realloc :: forall a b. Prim b => Ptr a -> IO (Ptr b)
- reallocBytes :: Ptr a -> Int -> IO (Ptr a)
- free :: Ptr a -> IO ()
- finalizerFree :: FinalizerPtr a
- mallocArray :: forall a. Prim a => Int -> IO (Ptr a)
- mallocArray0 :: forall a. Prim a => Int -> IO (Ptr a)
- allocaArray :: forall a b. Prim a => Int -> (Ptr a -> IO b) -> IO b
- allocaArray0 :: forall a b. Prim a => Int -> (Ptr a -> IO b) -> IO b
- reallocArray :: forall a. Prim a => Ptr a -> Int -> IO (Ptr a)
- reallocArray0 :: forall a. Prim a => Ptr a -> Int -> IO (Ptr a)
- callocArray :: forall a. Prim a => Int -> IO (Ptr a)
- callocArray0 :: forall a. Prim a => Int -> IO (Ptr a)
- peekArray :: forall a. Prim a => Int -> Ptr a -> IO (PrimArray a)
- peekArray0 :: forall a. (Prim a, Eq a) => a -> Ptr a -> IO (PrimArray a)
- pokeArray :: forall a. Prim a => Ptr a -> PrimArray a -> IO ()
- pokeArray0 :: forall a. Prim a => a -> Ptr a -> PrimArray a -> IO ()
- newArray :: forall a. Prim a => PrimArray a -> IO (Ptr a)
- newArray0 :: forall a. Prim a => a -> PrimArray a -> IO (Ptr a)
- withArray :: forall a b. Prim a => PrimArray a -> (Ptr a -> IO b) -> IO b
- withArray0 :: forall a b. Prim a => a -> PrimArray a -> (Ptr a -> IO b) -> IO b
- withArrayLen :: forall a b. Prim a => PrimArray a -> (Int -> Ptr a -> IO b) -> IO b
- withArrayLen0 :: forall a b. Prim a => a -> PrimArray a -> (Int -> Ptr a -> IO b) -> IO b
- copyArray :: forall a. Prim a => Ptr a -> Ptr a -> Int -> IO ()
- moveArray :: forall a. Prim a => Ptr a -> Ptr a -> Int -> IO ()
- lengthArray0 :: forall a. (Prim a, Eq a) => a -> Ptr a -> IO Int
- advancePtr :: forall a. Prim a => Ptr a -> Int -> Ptr a
- with :: forall a b. Prim a => a -> (Ptr a -> IO b) -> IO b
- new :: forall a. Prim a => a -> IO (Ptr a)
- maybeNew :: (a -> IO (Ptr b)) -> Maybe a -> IO (Ptr b)
- maybeWith :: (a -> (Ptr b -> IO c) -> IO c) -> Maybe a -> (Ptr b -> IO c) -> IO c
- maybePeek :: (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
- copyBytes :: Ptr a -> Ptr a -> Int -> IO ()
- moveBytes :: Ptr a -> Ptr a -> Int -> IO ()
- fillBytes :: Ptr a -> Word8 -> Int -> IO ()
Prim-Storable methods
peek :: forall a. Prim a => Ptr a -> IO a Source #
Read a value from the given memory location.
Note that the peek and poke functions might require properly
aligned addresses to function correctly. This is architecture
dependent; thus, portable code should ensure that when peeking
or poking values of some type a
, the alignment constraint for
a
, as given by the function alignment
is fulfilled.
peekElemOff :: forall a. Prim a => Ptr a -> Int -> IO a Source #
Read a value from a memory area regarded as an array of values
of the same kind. The first argument specifies the start address
of the array and the second the index into the array (the first
element of the array has index 0
). The following equality holds,
peekElemOff addr idx = fixIO $ \result -> peek (addr `plusPtr` (idx * sizeOf result))
Note that this is only a specification, not necessarily the concrete implementation of the function.
peekByteOff :: forall a. Prim a => Ptr Void -> Int -> IO a Source #
Read a value from a memory location given by a base address and offset. The following equality holds:
peekByteOff addr off = peek (addr `plusPtr` off)
poke :: forall a. Prim a => Ptr a -> a -> IO () Source #
Write the given value to the given memory location. Alignment
restrictions might apply; see peek
.
pokeElemOff :: forall a. Prim a => Ptr a -> Int -> a -> IO () Source #
Write a value to a memory area regarded as an array of values of the same kind. The following equality holds:
pokeElemOff addr idx x = poke (addr `plusPtr` (idx * sizeOf x)) x
pokeByteOff :: forall a. Prim a => Ptr Void -> Int -> a -> IO () Source #
Write a value to a memory location given by a base address and offset. The following equality holds:
pokeByteOff addr off x = poke (addr `plusPtr` off) x
Memory allocation
Local allocation
alloca :: forall a b. Prim a => (Ptr a -> IO b) -> IO b Source #
executes the computation alloca
ff
, passing as argument
a pointer to a temporarily allocated block of memory sufficient to
hold values of type a
.
The memory is freed when f
terminates (either normally or via an
exception), so the pointer passed to f
must not be used after this.
allocaBytes :: Int -> (Ptr a -> IO b) -> IO b #
executes the computation allocaBytes
n ff
, passing as argument
a pointer to a temporarily allocated block of memory of n
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.
The memory is freed when f
terminates (either normally or via an
exception), so the pointer passed to f
must not be used after this.
Dynamic allocation
malloc :: forall a. Prim a => IO (Ptr a) Source #
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 may be deallocated using free
or finalizerFree
when
no longer required.
mallocBytes :: Int -> IO (Ptr a) #
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.
The memory may be deallocated using free
or finalizerFree
when
no longer required.
calloc :: forall a. Prim a => IO (Ptr a) Source #
Like malloc
but memory is filled with bytes of value zero.
callocBytes :: Int -> IO (Ptr a) #
Llike mallocBytes
but memory is filled with bytes of value zero.
realloc :: forall a b. Prim b => Ptr a -> IO (Ptr b) Source #
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
aligned to hold values of type b
. The contents of the referenced
memory area will be the same as of the original pointer up to the
minimum of the original size and the size of values of type b
.
If the argument to realloc
is nullPtr
, realloc
behaves like
malloc
.
reallocBytes :: Ptr a -> Int -> IO (Ptr a) #
Resize a memory area that was allocated with malloc
or mallocBytes
to the given size. The returned pointer may refer to an entirely
different memory area, but will be sufficiently aligned for any of the
basic foreign types that fits into a memory block of the given size.
The contents of the referenced memory area will be the same as of
the original pointer up to the minimum of the original size and the
given size.
If the pointer argument to reallocBytes
is nullPtr
, reallocBytes
behaves like malloc
. If the requested size is 0, reallocBytes
behaves like free
.
Free a block of memory that was allocated with malloc
,
mallocBytes
, realloc
, reallocBytes
, new
or any of the new
X functions in Foreign.Marshal.Array or
Foreign.C.String.
finalizerFree :: FinalizerPtr a #
A pointer to a foreign function equivalent to free
, which may be
used as a finalizer (cf ForeignPtr
) for storage
allocated with malloc
, mallocBytes
, realloc
or reallocBytes
.
Marshalling arrays
Allocation
mallocArray :: forall a. Prim a => Int -> IO (Ptr a) Source #
Allocate storage for the given number of elements of a storable type
(like malloc
, but for multiple elements).
mallocArray0 :: forall a. Prim a => Int -> IO (Ptr a) Source #
Like mallocArray
, but add an extra position to hold a special
termination element.
allocaArray :: forall a b. Prim a => Int -> (Ptr a -> IO b) -> IO b Source #
Temporarily allocate space for the given number of elements
(like alloca
, but for multiple elements).
allocaArray0 :: forall a b. Prim a => Int -> (Ptr a -> IO b) -> IO b Source #
Like allocaArray
, but add an extra position to hold a special
termination element.
reallocArray0 :: forall a. Prim a => Ptr a -> Int -> IO (Ptr a) Source #
Adjust the size of an array, including an extra position for the terminating element.
callocArray :: forall a. Prim a => Int -> IO (Ptr a) Source #
Like mallocArray
, but allocated memory is filled with bytes of value zero.
callocArray0 :: forall a. Prim a => Int -> IO (Ptr a) Source #
Like mallocArray0
, but allocated memory is filled with bytes of value zero.
Marshalling
peekArray :: forall a. Prim a => Int -> Ptr a -> IO (PrimArray a) Source #
Convert an array of given length into a Haskell PrimArray
.
peekArray0 :: forall a. (Prim a, Eq a) => a -> Ptr a -> IO (PrimArray a) Source #
Convert an array terminated by the given terminator into a Haskell
PrimArray
.
pokeArray :: forall a. Prim a => Ptr a -> PrimArray a -> IO () Source #
Write the PrimArray
into memory at the given location.
pokeArray0 :: forall a. Prim a => a -> Ptr a -> PrimArray a -> IO () Source #
Write the PrimArray
into memory and terminate the elements
with a given terminating element.
Combined allocation and marshalling
newArray :: forall a. Prim a => PrimArray a -> IO (Ptr a) Source #
Write a PrimArray
into a newly allocated, consecutive
sequence of primitive values.
newArray0 :: forall a. Prim a => a -> PrimArray a -> IO (Ptr a) Source #
Write a PrimArray
into a newly allocated, consecutive
sequence of primitive values, where the end is fixed by
the given terminating element.
withArray :: forall a b. Prim a => PrimArray a -> (Ptr a -> IO b) -> IO b Source #
Temporarily store a PrimArray
in memory.
withArray0 :: forall a b. Prim a => a -> PrimArray a -> (Ptr a -> IO b) -> IO b Source #
Like withArray
, but a terminator indicates where the array ends.
withArrayLen0 :: forall a b. Prim a => a -> PrimArray a -> (Int -> Ptr a -> IO b) -> IO b Source #
Like withArrayLen
, but a terminator indicates where the array ends.
Copying
Copy the given number of elements from the source array into the destination array; the memory regions may not overlap.
Copy the given number of elements from the source array into the destination array; the memory regions may overlap.
Finding the length
Return the number of elements in an array, excluding the terminator
Indexing
advancePtr :: forall a. Prim a => Ptr a -> Int -> Ptr a Source #
Advance a pointer into an array by the given number of elements.
General marshalling utilities
Combined allocation and marshalling
with :: forall a b. Prim a => a -> (Ptr a -> IO b) -> IO b Source #
executes the computation with
val ff
, passing as argument
a pointer to a temporarily allocated block of memory into which
val
has been marshalled (the combination of alloca
and poke
).
The memory is freed when f
terminates (either normally or via an
exception), so the pointer passed to f
must not be used after this.
Marshalling of Maybe values
Haskellish interface to memcpy and memmove
copyBytes :: Ptr a -> Ptr a -> Int -> IO () #
Copies the given number of bytes from the second area (source) into the first (destination); the copied areas may not overlap
moveBytes :: Ptr a -> Ptr a -> Int -> IO () #
Copies the given number of bytes from the second area (source) into the first (destination); the copied areas may overlap