Safe Haskell | None |
---|---|
Language | Haskell98 |
Assorted utility functions for bindings.
- whenJust :: Monad m => Maybe a -> (a -> m ()) -> m ()
- maybeM :: Monad m => b -> Maybe a -> (a -> m b) -> m b
- maybeFromPtr :: Ptr a -> Maybe (Ptr a)
- mapFirst :: (a -> c) -> [(a, b)] -> [(c, b)]
- mapFirstA :: Applicative f => (a -> f c) -> [(a, b)] -> f [(c, b)]
- mapSecond :: (b -> c) -> [(a, b)] -> [(a, c)]
- mapSecondA :: Applicative f => (b -> f c) -> [(a, b)] -> f [(a, c)]
- convertIfNonNull :: Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
- callocBytes :: Int -> IO (Ptr a)
- callocBoxedBytes :: forall a. BoxedObject a => Int -> IO (Ptr a)
- callocMem :: forall a. Storable a => IO (Ptr a)
- allocBytes :: Integral a => a -> IO (Ptr b)
- allocMem :: forall a. Storable a => IO (Ptr a)
- freeMem :: Ptr a -> IO ()
- ptr_to_g_free :: FunPtr (Ptr a -> IO ())
- memcpy :: Ptr a -> Ptr b -> Int -> IO ()
- safeFreeFunPtr :: Ptr a -> IO ()
- safeFreeFunPtrPtr :: FunPtr (Ptr a -> IO ())
- maybeReleaseFunPtr :: Maybe (Ptr (FunPtr a)) -> IO ()
- checkUnexpectedReturnNULL :: Text -> Ptr a -> IO ()
- checkUnexpectedNothing :: Text -> IO (Maybe a) -> IO a
Documentation
whenJust :: Monad m => Maybe a -> (a -> m ()) -> m () Source
When the given value is of "Just a" form, execute the given action, otherwise do nothing.
maybeM :: Monad m => b -> Maybe a -> (a -> m b) -> m b Source
Like maybe
, but for actions on a monad, and with
slightly different argument order.
maybeFromPtr :: Ptr a -> Maybe (Ptr a) Source
mapFirst :: (a -> c) -> [(a, b)] -> [(c, b)] Source
Given a function and a list of two-tuples, apply the function to every first element of the tuples.
mapFirstA :: Applicative f => (a -> f c) -> [(a, b)] -> f [(c, b)] Source
Applicative version of mapFirst
.
mapSecondA :: Applicative f => (b -> f c) -> [(a, b)] -> f [(a, c)] Source
Applicative version of mapSecond
.
convertIfNonNull :: Ptr a -> (Ptr a -> IO b) -> IO (Maybe b) Source
Apply the given conversion action to the given pointer if it is
non-NULL, otherwise return Nothing
.
callocBytes :: Int -> IO (Ptr a) Source
Make a zero-filled allocation using the GLib allocator.
callocBoxedBytes :: forall a. BoxedObject a => Int -> IO (Ptr a) Source
Make a zero filled allocation of n bytes for a boxed object. The difference with a normal callocBytes is that the returned memory is allocated using whatever memory allocator g_boxed_copy uses, which in particular may well be different from a plain g_malloc. In particular g_slice_alloc is often used for allocating boxed objects, which are then freed using g_slice_free.
callocMem :: forall a. Storable a => IO (Ptr a) Source
Make a zero-filled allocation of enough size to hold the given
Storable
type, using the GLib allocator.
allocBytes :: Integral a => a -> IO (Ptr b) Source
Allocate the given number of bytes using the GLib allocator.
allocMem :: forall a. Storable a => IO (Ptr a) Source
Allocate space for the given Storable
using the GLib allocator.
ptr_to_g_free :: FunPtr (Ptr a -> IO ()) Source
Pointer to g_free
.
memcpy :: Ptr a -> Ptr b -> Int -> IO () Source
Copy memory into a destination (in the first argument) from a source (in the second argument).
safeFreeFunPtr :: Ptr a -> IO () Source
Same as freeHaskellFunPtr, but it does nothing when given a nullPtr.
safeFreeFunPtrPtr :: FunPtr (Ptr a -> IO ()) Source
A pointer to safeFreeFunPtr
.
maybeReleaseFunPtr :: Maybe (Ptr (FunPtr a)) -> IO () Source
If given a pointer to the memory location, free the FunPtr
at
that location, and then the pointer itself. Useful for freeing the
memory associated to callbacks which are called just once, with no
destroy notification.
checkUnexpectedReturnNULL :: Text -> Ptr a -> IO () Source
Check that the given pointer is not NULL. If it is, raise a
UnexpectedNullPointerReturn
exception.
checkUnexpectedNothing :: Text -> IO (Maybe a) -> IO a Source
An annotated version of fromJust
, which raises a
UnexpectedNullPointerReturn
in case it encounters a Nothing
.