{-# LINE 1 "Data/GI/Base/Utils.hsc" #-}
{-# LANGUAGE ScopedTypeVariables, TupleSections, OverloadedStrings,
FlexibleContexts, ConstraintKinds #-}
module Data.GI.Base.Utils
( whenJust
, maybeM
, maybeFromPtr
, mapFirst
, mapFirstA
, mapSecond
, mapSecondA
, convertIfNonNull
, convertFunPtrIfNonNull
, callocBytes
, callocBoxedBytes
, callocMem
, allocBytes
, allocMem
, freeMem
, ptr_to_g_free
, memcpy
, safeFreeFunPtr
, safeFreeFunPtrPtr
, maybeReleaseFunPtr
, checkUnexpectedReturnNULL
, checkUnexpectedNothing
) where
{-# LINE 34 "Data/GI/Base/Utils.hsc" #-}
import Control.Exception (throwIO)
import Control.Monad (void)
import qualified Data.Text as T
import Data.Monoid ((<>))
import Data.Word
import Foreign (peek)
import Foreign.C.Types (CSize(..))
import Foreign.Ptr (Ptr, nullPtr, FunPtr, nullFunPtr, freeHaskellFunPtr)
import Foreign.Storable (Storable(..))
import Data.GI.Base.BasicTypes (GType(..), CGType, BoxedObject(..),
UnexpectedNullPointerReturn(..))
import Data.GI.Base.CallStack (HasCallStack, callStack, prettyCallStack)
whenJust :: Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust (Just v) f = f v
whenJust Nothing _ = return ()
maybeM :: Monad m => b -> Maybe a -> (a -> m b) -> m b
maybeM d Nothing _ = return d
maybeM _ (Just v) action = action v
maybeFromPtr :: Ptr a -> Maybe (Ptr a)
maybeFromPtr ptr = if ptr == nullPtr
then Nothing
else Just ptr
mapFirst :: (a -> c) -> [(a,b)] -> [(c,b)]
mapFirst _ [] = []
mapFirst f ((x,y) : rest) = (f x, y) : mapFirst f rest
mapSecond :: (b -> c) -> [(a,b)] -> [(a,c)]
mapSecond _ [] = []
mapSecond f ((x,y) : rest) = (x, f y) : mapSecond f rest
mapFirstA :: Applicative f => (a -> f c) -> [(a,b)] -> f [(c,b)]
mapFirstA _ [] = pure []
mapFirstA f ((x,y) : rest) = (:) <$> ((,y) <$> f x) <*> mapFirstA f rest
mapSecondA :: Applicative f => (b -> f c) -> [(a,b)] -> f [(a,c)]
mapSecondA _ [] = pure []
mapSecondA f ((x,y) : rest) = (:) <$> ((x,) <$> f y) <*> mapSecondA f rest
convertIfNonNull :: Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull ptr convert = if ptr == nullPtr
then return Nothing
else Just <$> convert ptr
convertFunPtrIfNonNull :: FunPtr a -> (FunPtr a -> IO b) -> IO (Maybe b)
convertFunPtrIfNonNull ptr convert = if ptr == nullFunPtr
then return Nothing
else Just <$> convert ptr
foreign import ccall "g_malloc0" g_malloc0 ::
Word64 -> IO (Ptr a)
{-# LINE 106 "Data/GI/Base/Utils.hsc" #-}
{-# INLINE callocBytes #-}
callocBytes :: Int -> IO (Ptr a)
callocBytes n = g_malloc0 (fromIntegral n)
{-# INLINE callocMem #-}
callocMem :: forall a. Storable a => IO (Ptr a)
callocMem = g_malloc0 $ (fromIntegral . sizeOf) (undefined :: a)
foreign import ccall "g_boxed_copy" g_boxed_copy ::
CGType -> Ptr a -> IO (Ptr a)
callocBoxedBytes :: forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes n = do
ptr <- callocBytes n
GType cgtype <- boxedType (undefined :: a)
result <- g_boxed_copy cgtype ptr
freeMem ptr
return result
foreign import ccall "g_malloc" g_malloc ::
Word64 -> IO (Ptr a)
{-# LINE 137 "Data/GI/Base/Utils.hsc" #-}
{-# INLINE allocBytes #-}
allocBytes :: Integral a => a -> IO (Ptr b)
allocBytes n = g_malloc (fromIntegral n)
{-# INLINE allocMem #-}
allocMem :: forall a. Storable a => IO (Ptr a)
allocMem = g_malloc $ (fromIntegral . sizeOf) (undefined :: a)
foreign import ccall "g_free" freeMem :: Ptr a -> IO ()
foreign import ccall "&g_free" ptr_to_g_free :: FunPtr (Ptr a -> IO ())
foreign import ccall unsafe "string.h memcpy" _memcpy :: Ptr a -> Ptr b -> CSize -> IO (Ptr ())
{-# INLINE memcpy #-}
memcpy :: Ptr a -> Ptr b -> Int -> IO ()
memcpy dest src n = void $ _memcpy dest src (fromIntegral n)
foreign import ccall "safeFreeFunPtr" safeFreeFunPtr ::
Ptr a -> IO ()
foreign import ccall "& safeFreeFunPtr" safeFreeFunPtrPtr ::
FunPtr (Ptr a -> IO ())
maybeReleaseFunPtr :: Maybe (Ptr (FunPtr a)) -> IO ()
maybeReleaseFunPtr Nothing = return ()
maybeReleaseFunPtr (Just f) = do
peek f >>= freeHaskellFunPtr
freeMem f
checkUnexpectedReturnNULL :: HasCallStack => T.Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL fnName ptr
| ptr == nullPtr =
throwIO (UnexpectedNullPointerReturn {
nullPtrErrorMsg = "Received unexpected nullPtr in \""
<> fnName <> "\".\n" <>
"This is a bug in the introspection data, please report it at\nhttps://github.com/haskell-gi/haskell-gi/issues\n" <>
T.pack (prettyCallStack callStack)
})
| otherwise = return ()
checkUnexpectedNothing :: HasCallStack => T.Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing fnName action = do
result <- action
case result of
Just r -> return r
Nothing -> throwIO (UnexpectedNullPointerReturn {
nullPtrErrorMsg = "Received unexpected nullPtr in \""
<> fnName <> "\".\n" <>
"This is a bug in the introspection data, please report it at\nhttps://github.com/haskell-gi/haskell-gi/issues\n" <>
T.pack (prettyCallStack callStack)
})