{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.GLib.Structs.Bytes
(
Bytes(..) ,
#if defined(ENABLE_OVERLOADING)
ResolveBytesMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
BytesCompareMethodInfo ,
#endif
bytesCompare ,
#if defined(ENABLE_OVERLOADING)
BytesEqualMethodInfo ,
#endif
bytesEqual ,
#if defined(ENABLE_OVERLOADING)
BytesGetDataMethodInfo ,
#endif
bytesGetData ,
#if defined(ENABLE_OVERLOADING)
BytesGetSizeMethodInfo ,
#endif
bytesGetSize ,
#if defined(ENABLE_OVERLOADING)
BytesHashMethodInfo ,
#endif
bytesHash ,
bytesNew ,
#if defined(ENABLE_OVERLOADING)
BytesNewFromBytesMethodInfo ,
#endif
bytesNewFromBytes ,
bytesNewTake ,
#if defined(ENABLE_OVERLOADING)
BytesRefMethodInfo ,
#endif
bytesRef ,
#if defined(ENABLE_OVERLOADING)
BytesUnrefMethodInfo ,
#endif
bytesUnref ,
#if defined(ENABLE_OVERLOADING)
BytesUnrefToArrayMethodInfo ,
#endif
bytesUnrefToArray ,
#if defined(ENABLE_OVERLOADING)
BytesUnrefToDataMethodInfo ,
#endif
bytesUnrefToData ,
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
newtype Bytes = Bytes (SP.ManagedPtr Bytes)
deriving (Bytes -> Bytes -> Bool
(Bytes -> Bytes -> Bool) -> (Bytes -> Bytes -> Bool) -> Eq Bytes
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Bytes -> Bytes -> Bool
$c/= :: Bytes -> Bytes -> Bool
== :: Bytes -> Bytes -> Bool
$c== :: Bytes -> Bytes -> Bool
Eq)
instance SP.ManagedPtrNewtype Bytes where
toManagedPtr :: Bytes -> ManagedPtr Bytes
toManagedPtr (Bytes ManagedPtr Bytes
p) = ManagedPtr Bytes
p
foreign import ccall "g_bytes_get_type" c_g_bytes_get_type ::
IO GType
type instance O.ParentTypes Bytes = '[]
instance O.HasParentTypes Bytes
instance B.Types.TypedObject Bytes where
glibType :: IO GType
glibType = IO GType
c_g_bytes_get_type
instance B.Types.GBoxed Bytes
instance B.GValue.IsGValue Bytes where
toGValue :: Bytes -> IO GValue
toGValue Bytes
o = do
GType
gtype <- IO GType
c_g_bytes_get_type
Bytes -> (Ptr Bytes -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Bytes
o (GType -> (GValue -> Ptr Bytes -> IO ()) -> Ptr Bytes -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr Bytes -> IO ()
forall a. GValue -> Ptr a -> IO ()
B.GValue.set_boxed)
fromGValue :: GValue -> IO Bytes
fromGValue GValue
gv = do
Ptr Bytes
ptr <- GValue -> IO (Ptr Bytes)
forall b. GValue -> IO (Ptr b)
B.GValue.get_boxed GValue
gv :: IO (Ptr Bytes)
(ManagedPtr Bytes -> Bytes) -> Ptr Bytes -> IO Bytes
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr Bytes -> Bytes
Bytes Ptr Bytes
ptr
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Bytes
type instance O.AttributeList Bytes = BytesAttributeList
type BytesAttributeList = ('[ ] :: [(Symbol, *)])
#endif
foreign import ccall "g_bytes_new" g_bytes_new ::
Ptr Word8 ->
Word64 ->
IO (Ptr Bytes)
bytesNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
Maybe (ByteString)
-> m Bytes
bytesNew :: Maybe ByteString -> m Bytes
bytesNew Maybe ByteString
data_ = IO Bytes -> m Bytes
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bytes -> m Bytes) -> IO Bytes -> m Bytes
forall a b. (a -> b) -> a -> b
$ do
let size :: Word64
size = case Maybe ByteString
data_ of
Maybe ByteString
Nothing -> Word64
0
Just ByteString
jData_ -> Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word64) -> Int -> Word64
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
jData_
Ptr Word8
maybeData_ <- case Maybe ByteString
data_ of
Maybe ByteString
Nothing -> Ptr Word8 -> IO (Ptr Word8)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Word8
forall a. Ptr a
nullPtr
Just ByteString
jData_ -> do
Ptr Word8
jData_' <- ByteString -> IO (Ptr Word8)
packByteString ByteString
jData_
Ptr Word8 -> IO (Ptr Word8)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Word8
jData_'
Ptr Bytes
result <- Ptr Word8 -> Word64 -> IO (Ptr Bytes)
g_bytes_new Ptr Word8
maybeData_ Word64
size
Text -> Ptr Bytes -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"bytesNew" Ptr Bytes
result
Bytes
result' <- ((ManagedPtr Bytes -> Bytes) -> Ptr Bytes -> IO Bytes
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Bytes -> Bytes
Bytes) Ptr Bytes
result
Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
maybeData_
Bytes -> IO Bytes
forall (m :: * -> *) a. Monad m => a -> m a
return Bytes
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_bytes_new_take" g_bytes_new_take ::
Ptr Word8 ->
Word64 ->
IO (Ptr Bytes)
bytesNewTake ::
(B.CallStack.HasCallStack, MonadIO m) =>
Maybe (ByteString)
-> m Bytes
bytesNewTake :: Maybe ByteString -> m Bytes
bytesNewTake Maybe ByteString
data_ = IO Bytes -> m Bytes
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bytes -> m Bytes) -> IO Bytes -> m Bytes
forall a b. (a -> b) -> a -> b
$ do
let size :: Word64
size = case Maybe ByteString
data_ of
Maybe ByteString
Nothing -> Word64
0
Just ByteString
jData_ -> Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word64) -> Int -> Word64
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
jData_
Ptr Word8
maybeData_ <- case Maybe ByteString
data_ of
Maybe ByteString
Nothing -> Ptr Word8 -> IO (Ptr Word8)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Word8
forall a. Ptr a
nullPtr
Just ByteString
jData_ -> do
Ptr Word8
jData_' <- ByteString -> IO (Ptr Word8)
packByteString ByteString
jData_
Ptr Word8 -> IO (Ptr Word8)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Word8
jData_'
Ptr Bytes
result <- Ptr Word8 -> Word64 -> IO (Ptr Bytes)
g_bytes_new_take Ptr Word8
maybeData_ Word64
size
Text -> Ptr Bytes -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"bytesNewTake" Ptr Bytes
result
Bytes
result' <- ((ManagedPtr Bytes -> Bytes) -> Ptr Bytes -> IO Bytes
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Bytes -> Bytes
Bytes) Ptr Bytes
result
Bytes -> IO Bytes
forall (m :: * -> *) a. Monad m => a -> m a
return Bytes
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_bytes_compare" g_bytes_compare ::
Ptr Bytes ->
Ptr Bytes ->
IO Int32
bytesCompare ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bytes
-> Bytes
-> m Int32
bytesCompare :: Bytes -> Bytes -> m Int32
bytesCompare Bytes
bytes1 Bytes
bytes2 = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
Ptr Bytes
bytes1' <- Bytes -> IO (Ptr Bytes)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bytes
bytes1
Ptr Bytes
bytes2' <- Bytes -> IO (Ptr Bytes)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bytes
bytes2
Int32
result <- Ptr Bytes -> Ptr Bytes -> IO Int32
g_bytes_compare Ptr Bytes
bytes1' Ptr Bytes
bytes2'
Bytes -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bytes
bytes1
Bytes -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bytes
bytes2
Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data BytesCompareMethodInfo
instance (signature ~ (Bytes -> m Int32), MonadIO m) => O.MethodInfo BytesCompareMethodInfo Bytes signature where
overloadedMethod = bytesCompare
#endif
foreign import ccall "g_bytes_equal" g_bytes_equal ::
Ptr Bytes ->
Ptr Bytes ->
IO CInt
bytesEqual ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bytes
-> Bytes
-> m Bool
bytesEqual :: Bytes -> Bytes -> m Bool
bytesEqual Bytes
bytes1 Bytes
bytes2 = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr Bytes
bytes1' <- Bytes -> IO (Ptr Bytes)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bytes
bytes1
Ptr Bytes
bytes2' <- Bytes -> IO (Ptr Bytes)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bytes
bytes2
CInt
result <- Ptr Bytes -> Ptr Bytes -> IO CInt
g_bytes_equal Ptr Bytes
bytes1' Ptr Bytes
bytes2'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
Bytes -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bytes
bytes1
Bytes -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bytes
bytes2
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data BytesEqualMethodInfo
instance (signature ~ (Bytes -> m Bool), MonadIO m) => O.MethodInfo BytesEqualMethodInfo Bytes signature where
overloadedMethod = bytesEqual
#endif
foreign import ccall "g_bytes_get_data" g_bytes_get_data ::
Ptr Bytes ->
Ptr Word64 ->
IO (Ptr Word8)
bytesGetData ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bytes
-> m (Maybe ByteString)
bytesGetData :: Bytes -> m (Maybe ByteString)
bytesGetData Bytes
bytes = IO (Maybe ByteString) -> m (Maybe ByteString)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe ByteString) -> m (Maybe ByteString))
-> IO (Maybe ByteString) -> m (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ do
Ptr Bytes
bytes' <- Bytes -> IO (Ptr Bytes)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bytes
bytes
Ptr Word64
size <- IO (Ptr Word64)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word64)
Ptr Word8
result <- Ptr Bytes -> Ptr Word64 -> IO (Ptr Word8)
g_bytes_get_data Ptr Bytes
bytes' Ptr Word64
size
Word64
size' <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek Ptr Word64
size
Maybe ByteString
maybeResult <- Ptr Word8 -> (Ptr Word8 -> IO ByteString) -> IO (Maybe ByteString)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Word8
result ((Ptr Word8 -> IO ByteString) -> IO (Maybe ByteString))
-> (Ptr Word8 -> IO ByteString) -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
result' -> do
ByteString
result'' <- (Word64 -> Ptr Word8 -> IO ByteString
forall a. Integral a => a -> Ptr Word8 -> IO ByteString
unpackByteStringWithLength Word64
size') Ptr Word8
result'
ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
result''
Bytes -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bytes
bytes
Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
size
Maybe ByteString -> IO (Maybe ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ByteString
maybeResult
#if defined(ENABLE_OVERLOADING)
data BytesGetDataMethodInfo
instance (signature ~ (m (Maybe ByteString)), MonadIO m) => O.MethodInfo BytesGetDataMethodInfo Bytes signature where
overloadedMethod = bytesGetData
#endif
foreign import ccall "g_bytes_get_size" g_bytes_get_size ::
Ptr Bytes ->
IO Word64
bytesGetSize ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bytes
-> m Word64
bytesGetSize :: Bytes -> m Word64
bytesGetSize Bytes
bytes = IO Word64 -> m Word64
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word64 -> m Word64) -> IO Word64 -> m Word64
forall a b. (a -> b) -> a -> b
$ do
Ptr Bytes
bytes' <- Bytes -> IO (Ptr Bytes)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bytes
bytes
Word64
result <- Ptr Bytes -> IO Word64
g_bytes_get_size Ptr Bytes
bytes'
Bytes -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bytes
bytes
Word64 -> IO Word64
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
result
#if defined(ENABLE_OVERLOADING)
data BytesGetSizeMethodInfo
instance (signature ~ (m Word64), MonadIO m) => O.MethodInfo BytesGetSizeMethodInfo Bytes signature where
overloadedMethod = bytesGetSize
#endif
foreign import ccall "g_bytes_hash" g_bytes_hash ::
Ptr Bytes ->
IO Word32
bytesHash ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bytes
-> m Word32
bytesHash :: Bytes -> m Word32
bytesHash Bytes
bytes = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
Ptr Bytes
bytes' <- Bytes -> IO (Ptr Bytes)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bytes
bytes
Word32
result <- Ptr Bytes -> IO Word32
g_bytes_hash Ptr Bytes
bytes'
Bytes -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bytes
bytes
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
#if defined(ENABLE_OVERLOADING)
data BytesHashMethodInfo
instance (signature ~ (m Word32), MonadIO m) => O.MethodInfo BytesHashMethodInfo Bytes signature where
overloadedMethod = bytesHash
#endif
foreign import ccall "g_bytes_new_from_bytes" g_bytes_new_from_bytes ::
Ptr Bytes ->
Word64 ->
Word64 ->
IO (Ptr Bytes)
bytesNewFromBytes ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bytes
-> Word64
-> Word64
-> m Bytes
bytesNewFromBytes :: Bytes -> Word64 -> Word64 -> m Bytes
bytesNewFromBytes Bytes
bytes Word64
offset Word64
length_ = IO Bytes -> m Bytes
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bytes -> m Bytes) -> IO Bytes -> m Bytes
forall a b. (a -> b) -> a -> b
$ do
Ptr Bytes
bytes' <- Bytes -> IO (Ptr Bytes)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bytes
bytes
Ptr Bytes
result <- Ptr Bytes -> Word64 -> Word64 -> IO (Ptr Bytes)
g_bytes_new_from_bytes Ptr Bytes
bytes' Word64
offset Word64
length_
Text -> Ptr Bytes -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"bytesNewFromBytes" Ptr Bytes
result
Bytes
result' <- ((ManagedPtr Bytes -> Bytes) -> Ptr Bytes -> IO Bytes
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Bytes -> Bytes
Bytes) Ptr Bytes
result
Bytes -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bytes
bytes
Bytes -> IO Bytes
forall (m :: * -> *) a. Monad m => a -> m a
return Bytes
result'
#if defined(ENABLE_OVERLOADING)
data BytesNewFromBytesMethodInfo
instance (signature ~ (Word64 -> Word64 -> m Bytes), MonadIO m) => O.MethodInfo BytesNewFromBytesMethodInfo Bytes signature where
overloadedMethod = bytesNewFromBytes
#endif
foreign import ccall "g_bytes_ref" g_bytes_ref ::
Ptr Bytes ->
IO (Ptr Bytes)
bytesRef ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bytes
-> m Bytes
bytesRef :: Bytes -> m Bytes
bytesRef Bytes
bytes = IO Bytes -> m Bytes
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bytes -> m Bytes) -> IO Bytes -> m Bytes
forall a b. (a -> b) -> a -> b
$ do
Ptr Bytes
bytes' <- Bytes -> IO (Ptr Bytes)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bytes
bytes
Ptr Bytes
result <- Ptr Bytes -> IO (Ptr Bytes)
g_bytes_ref Ptr Bytes
bytes'
Text -> Ptr Bytes -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"bytesRef" Ptr Bytes
result
Bytes
result' <- ((ManagedPtr Bytes -> Bytes) -> Ptr Bytes -> IO Bytes
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Bytes -> Bytes
Bytes) Ptr Bytes
result
Bytes -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bytes
bytes
Bytes -> IO Bytes
forall (m :: * -> *) a. Monad m => a -> m a
return Bytes
result'
#if defined(ENABLE_OVERLOADING)
data BytesRefMethodInfo
instance (signature ~ (m Bytes), MonadIO m) => O.MethodInfo BytesRefMethodInfo Bytes signature where
overloadedMethod = bytesRef
#endif
foreign import ccall "g_bytes_unref" g_bytes_unref ::
Ptr Bytes ->
IO ()
bytesUnref ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bytes
-> m ()
bytesUnref :: Bytes -> m ()
bytesUnref Bytes
bytes = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Bytes
bytes' <- Bytes -> IO (Ptr Bytes)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bytes
bytes
Ptr Bytes -> IO ()
g_bytes_unref Ptr Bytes
bytes'
Bytes -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bytes
bytes
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data BytesUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo BytesUnrefMethodInfo Bytes signature where
overloadedMethod = bytesUnref
#endif
foreign import ccall "g_bytes_unref_to_array" g_bytes_unref_to_array ::
Ptr Bytes ->
IO (Ptr GByteArray)
bytesUnrefToArray ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bytes
-> m ByteString
bytesUnrefToArray :: Bytes -> m ByteString
bytesUnrefToArray Bytes
bytes = IO ByteString -> m ByteString
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ByteString -> m ByteString) -> IO ByteString -> m ByteString
forall a b. (a -> b) -> a -> b
$ do
Ptr Bytes
bytes' <- Bytes -> IO (Ptr Bytes)
forall a. (HasCallStack, GBoxed a) => a -> IO (Ptr a)
B.ManagedPtr.disownBoxed Bytes
bytes
Ptr GByteArray
result <- Ptr Bytes -> IO (Ptr GByteArray)
g_bytes_unref_to_array Ptr Bytes
bytes'
Text -> Ptr GByteArray -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"bytesUnrefToArray" Ptr GByteArray
result
ByteString
result' <- Ptr GByteArray -> IO ByteString
unpackGByteArray Ptr GByteArray
result
Ptr GByteArray -> IO ()
unrefGByteArray Ptr GByteArray
result
Bytes -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bytes
bytes
ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
result'
#if defined(ENABLE_OVERLOADING)
data BytesUnrefToArrayMethodInfo
instance (signature ~ (m ByteString), MonadIO m) => O.MethodInfo BytesUnrefToArrayMethodInfo Bytes signature where
overloadedMethod = bytesUnrefToArray
#endif
foreign import ccall "g_bytes_unref_to_data" g_bytes_unref_to_data ::
Ptr Bytes ->
Ptr Word64 ->
IO (Ptr Word8)
bytesUnrefToData ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bytes
-> m ByteString
bytesUnrefToData :: Bytes -> m ByteString
bytesUnrefToData Bytes
bytes = IO ByteString -> m ByteString
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ByteString -> m ByteString) -> IO ByteString -> m ByteString
forall a b. (a -> b) -> a -> b
$ do
Ptr Bytes
bytes' <- Bytes -> IO (Ptr Bytes)
forall a. (HasCallStack, GBoxed a) => a -> IO (Ptr a)
B.ManagedPtr.disownBoxed Bytes
bytes
Ptr Word64
size <- IO (Ptr Word64)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word64)
Ptr Word8
result <- Ptr Bytes -> Ptr Word64 -> IO (Ptr Word8)
g_bytes_unref_to_data Ptr Bytes
bytes' Ptr Word64
size
Word64
size' <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek Ptr Word64
size
Text -> Ptr Word8 -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"bytesUnrefToData" Ptr Word8
result
ByteString
result' <- (Word64 -> Ptr Word8 -> IO ByteString
forall a. Integral a => a -> Ptr Word8 -> IO ByteString
unpackByteStringWithLength Word64
size') Ptr Word8
result
Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
result
Bytes -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bytes
bytes
Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
size
ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
result'
#if defined(ENABLE_OVERLOADING)
data BytesUnrefToDataMethodInfo
instance (signature ~ (m ByteString), MonadIO m) => O.MethodInfo BytesUnrefToDataMethodInfo Bytes signature where
overloadedMethod = bytesUnrefToData
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveBytesMethod (t :: Symbol) (o :: *) :: * where
ResolveBytesMethod "compare" o = BytesCompareMethodInfo
ResolveBytesMethod "equal" o = BytesEqualMethodInfo
ResolveBytesMethod "hash" o = BytesHashMethodInfo
ResolveBytesMethod "newFromBytes" o = BytesNewFromBytesMethodInfo
ResolveBytesMethod "ref" o = BytesRefMethodInfo
ResolveBytesMethod "unref" o = BytesUnrefMethodInfo
ResolveBytesMethod "unrefToArray" o = BytesUnrefToArrayMethodInfo
ResolveBytesMethod "unrefToData" o = BytesUnrefToDataMethodInfo
ResolveBytesMethod "getData" o = BytesGetDataMethodInfo
ResolveBytesMethod "getSize" o = BytesGetSizeMethodInfo
ResolveBytesMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveBytesMethod t Bytes, O.MethodInfo info Bytes p) => OL.IsLabel t (Bytes -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif