{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Contains the public fields of a GByteArray.

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.GLib.Structs.ByteArray
    ( 

-- * Exported types
    ByteArray(..)                           ,
    newZeroByteArray                        ,
    noByteArray                             ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveByteArrayMethod                  ,
#endif


-- ** free #method:free#

    byteArrayFree                           ,


-- ** freeToBytes #method:freeToBytes#

    byteArrayFreeToBytes                    ,


-- ** new #method:new#

    byteArrayNew                            ,


-- ** newTake #method:newTake#

    byteArrayNewTake                        ,


-- ** unref #method:unref#

    byteArrayUnref                          ,




 -- * Properties
-- ** data #attr:data#
-- | a pointer to the element data. The data may be moved as
--     elements are added to the t'GI.GLib.Structs.ByteArray.ByteArray'

#if defined(ENABLE_OVERLOADING)
    byteArray_data                          ,
#endif
    getByteArrayData                        ,
    setByteArrayData                        ,


-- ** len #attr:len#
-- | the number of elements in the t'GI.GLib.Structs.ByteArray.ByteArray'

#if defined(ENABLE_OVERLOADING)
    byteArray_len                           ,
#endif
    getByteArrayLen                         ,
    setByteArrayLen                         ,




    ) 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.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 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

import {-# SOURCE #-} qualified GI.GLib.Structs.Bytes as GLib.Bytes

-- | Memory-managed wrapper type.
newtype ByteArray = ByteArray (ManagedPtr ByteArray)
    deriving (ByteArray -> ByteArray -> Bool
(ByteArray -> ByteArray -> Bool)
-> (ByteArray -> ByteArray -> Bool) -> Eq ByteArray
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ByteArray -> ByteArray -> Bool
$c/= :: ByteArray -> ByteArray -> Bool
== :: ByteArray -> ByteArray -> Bool
$c== :: ByteArray -> ByteArray -> Bool
Eq)
foreign import ccall "g_byte_array_get_type" c_g_byte_array_get_type :: 
    IO GType

instance BoxedObject ByteArray where
    boxedType :: ByteArray -> IO GType
boxedType _ = IO GType
c_g_byte_array_get_type

-- | Convert 'ByteArray' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue ByteArray where
    toGValue :: ByteArray -> IO GValue
toGValue o :: ByteArray
o = do
        GType
gtype <- IO GType
c_g_byte_array_get_type
        ByteArray -> (Ptr ByteArray -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr ByteArray
o (GType
-> (GValue -> Ptr ByteArray -> IO ()) -> Ptr ByteArray -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr ByteArray -> IO ()
forall a. GValue -> Ptr a -> IO ()
B.GValue.set_boxed)
        
    fromGValue :: GValue -> IO ByteArray
fromGValue gv :: GValue
gv = do
        Ptr ByteArray
ptr <- GValue -> IO (Ptr ByteArray)
forall b. GValue -> IO (Ptr b)
B.GValue.get_boxed GValue
gv :: IO (Ptr ByteArray)
        (ManagedPtr ByteArray -> ByteArray)
-> Ptr ByteArray -> IO ByteArray
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr ByteArray -> ByteArray
ByteArray Ptr ByteArray
ptr
        
    

-- | Construct a `ByteArray` struct initialized to zero.
newZeroByteArray :: MonadIO m => m ByteArray
newZeroByteArray :: m ByteArray
newZeroByteArray = IO ByteArray -> m ByteArray
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ByteArray -> m ByteArray) -> IO ByteArray -> m ByteArray
forall a b. (a -> b) -> a -> b
$ Int -> IO (Ptr ByteArray)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 16 IO (Ptr ByteArray)
-> (Ptr ByteArray -> IO ByteArray) -> IO ByteArray
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr ByteArray -> ByteArray)
-> Ptr ByteArray -> IO ByteArray
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr ByteArray -> ByteArray
ByteArray

instance tag ~ 'AttrSet => Constructible ByteArray tag where
    new :: (ManagedPtr ByteArray -> ByteArray)
-> [AttrOp ByteArray tag] -> m ByteArray
new _ attrs :: [AttrOp ByteArray tag]
attrs = do
        ByteArray
o <- m ByteArray
forall (m :: * -> *). MonadIO m => m ByteArray
newZeroByteArray
        ByteArray -> [AttrOp ByteArray 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set ByteArray
o [AttrOp ByteArray tag]
[AttrOp ByteArray 'AttrSet]
attrs
        ByteArray -> m ByteArray
forall (m :: * -> *) a. Monad m => a -> m a
return ByteArray
o


-- | A convenience alias for `Nothing` :: `Maybe` `ByteArray`.
noByteArray :: Maybe ByteArray
noByteArray :: Maybe ByteArray
noByteArray = Maybe ByteArray
forall a. Maybe a
Nothing

-- | Get the value of the “@data@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' byteArray #data
-- @
getByteArrayData :: MonadIO m => ByteArray -> m Word8
getByteArrayData :: ByteArray -> m Word8
getByteArrayData s :: ByteArray
s = IO Word8 -> m Word8
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word8 -> m Word8) -> IO Word8 -> m Word8
forall a b. (a -> b) -> a -> b
$ ByteArray -> (Ptr ByteArray -> IO Word8) -> IO Word8
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ByteArray
s ((Ptr ByteArray -> IO Word8) -> IO Word8)
-> (Ptr ByteArray -> IO Word8) -> IO Word8
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr ByteArray
ptr -> do
    Word8
val <- Ptr Word8 -> IO Word8
forall a. Storable a => Ptr a -> IO a
peek (Ptr ByteArray
ptr Ptr ByteArray -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) :: IO Word8
    Word8 -> IO Word8
forall (m :: * -> *) a. Monad m => a -> m a
return Word8
val

-- | Set the value of the “@data@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' byteArray [ #data 'Data.GI.Base.Attributes.:=' value ]
-- @
setByteArrayData :: MonadIO m => ByteArray -> Word8 -> m ()
setByteArrayData :: ByteArray -> Word8 -> m ()
setByteArrayData s :: ByteArray
s val :: Word8
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ ByteArray -> (Ptr ByteArray -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ByteArray
s ((Ptr ByteArray -> IO ()) -> IO ())
-> (Ptr ByteArray -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr ByteArray
ptr -> do
    Ptr Word8 -> Word8 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ByteArray
ptr Ptr ByteArray -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) (Word8
val :: Word8)

#if defined(ENABLE_OVERLOADING)
data ByteArrayDataFieldInfo
instance AttrInfo ByteArrayDataFieldInfo where
    type AttrBaseTypeConstraint ByteArrayDataFieldInfo = (~) ByteArray
    type AttrAllowedOps ByteArrayDataFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ByteArrayDataFieldInfo = (~) Word8
    type AttrTransferTypeConstraint ByteArrayDataFieldInfo = (~)Word8
    type AttrTransferType ByteArrayDataFieldInfo = Word8
    type AttrGetType ByteArrayDataFieldInfo = Word8
    type AttrLabel ByteArrayDataFieldInfo = "data"
    type AttrOrigin ByteArrayDataFieldInfo = ByteArray
    attrGet = getByteArrayData
    attrSet = setByteArrayData
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

byteArray_data :: AttrLabelProxy "data"
byteArray_data = AttrLabelProxy

#endif


-- | Get the value of the “@len@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' byteArray #len
-- @
getByteArrayLen :: MonadIO m => ByteArray -> m Word32
getByteArrayLen :: ByteArray -> m Word32
getByteArrayLen s :: ByteArray
s = 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
$ ByteArray -> (Ptr ByteArray -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ByteArray
s ((Ptr ByteArray -> IO Word32) -> IO Word32)
-> (Ptr ByteArray -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr ByteArray
ptr -> do
    Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr ByteArray
ptr Ptr ByteArray -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) :: IO Word32
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val

-- | Set the value of the “@len@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' byteArray [ #len 'Data.GI.Base.Attributes.:=' value ]
-- @
setByteArrayLen :: MonadIO m => ByteArray -> Word32 -> m ()
setByteArrayLen :: ByteArray -> Word32 -> m ()
setByteArrayLen s :: ByteArray
s val :: Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ ByteArray -> (Ptr ByteArray -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ByteArray
s ((Ptr ByteArray -> IO ()) -> IO ())
-> (Ptr ByteArray -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr ByteArray
ptr -> do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ByteArray
ptr Ptr ByteArray -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) (Word32
val :: Word32)

#if defined(ENABLE_OVERLOADING)
data ByteArrayLenFieldInfo
instance AttrInfo ByteArrayLenFieldInfo where
    type AttrBaseTypeConstraint ByteArrayLenFieldInfo = (~) ByteArray
    type AttrAllowedOps ByteArrayLenFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ByteArrayLenFieldInfo = (~) Word32
    type AttrTransferTypeConstraint ByteArrayLenFieldInfo = (~)Word32
    type AttrTransferType ByteArrayLenFieldInfo = Word32
    type AttrGetType ByteArrayLenFieldInfo = Word32
    type AttrLabel ByteArrayLenFieldInfo = "len"
    type AttrOrigin ByteArrayLenFieldInfo = ByteArray
    attrGet = getByteArrayLen
    attrSet = setByteArrayLen
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

byteArray_len :: AttrLabelProxy "len"
byteArray_len = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ByteArray
type instance O.AttributeList ByteArray = ByteArrayAttributeList
type ByteArrayAttributeList = ('[ '("data", ByteArrayDataFieldInfo), '("len", ByteArrayLenFieldInfo)] :: [(Symbol, *)])
#endif

-- method ByteArray::free
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "array"
--           , argType = TByteArray
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GByteArray" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "free_segment"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "if %TRUE the actual byte data is freed as well"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt8)
-- throws : False
-- Skip return : False

foreign import ccall "g_byte_array_free" g_byte_array_free :: 
    Ptr GByteArray ->                       -- array : TByteArray
    CInt ->                                 -- free_segment : TBasicType TBoolean
    IO Word8

-- | Frees the memory allocated by the t'GI.GLib.Structs.ByteArray.ByteArray'. If /@freeSegment@/ is
-- 'P.True' it frees the actual byte data. If the reference count of
-- /@array@/ is greater than one, the t'GI.GLib.Structs.ByteArray.ByteArray' wrapper is preserved but
-- the size of /@array@/ will be set to zero.
byteArrayFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteString
    -- ^ /@array@/: a t'GI.GLib.Structs.ByteArray.ByteArray'
    -> Bool
    -- ^ /@freeSegment@/: if 'P.True' the actual byte data is freed as well
    -> m Word8
    -- ^ __Returns:__ the element data if /@freeSegment@/ is 'P.False', otherwise
    --          'P.Nothing'.  The element data should be freed using 'GI.GLib.Functions.free'.
byteArrayFree :: ByteString -> Bool -> m Word8
byteArrayFree array :: ByteString
array freeSegment :: Bool
freeSegment = IO Word8 -> m Word8
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word8 -> m Word8) -> IO Word8 -> m Word8
forall a b. (a -> b) -> a -> b
$ do
    Ptr GByteArray
array' <- ByteString -> IO (Ptr GByteArray)
packGByteArray ByteString
array
    let freeSegment' :: CInt
freeSegment' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
freeSegment
    Word8
result <- Ptr GByteArray -> CInt -> IO Word8
g_byte_array_free Ptr GByteArray
array' CInt
freeSegment'
    Ptr GByteArray -> IO ()
unrefGByteArray Ptr GByteArray
array'
    Word8 -> IO Word8
forall (m :: * -> *) a. Monad m => a -> m a
return Word8
result

#if defined(ENABLE_OVERLOADING)
#endif

-- method ByteArray::free_to_bytes
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "array"
--           , argType = TByteArray
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GByteArray" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "Bytes" })
-- throws : False
-- Skip return : False

foreign import ccall "g_byte_array_free_to_bytes" g_byte_array_free_to_bytes :: 
    Ptr GByteArray ->                       -- array : TByteArray
    IO (Ptr GLib.Bytes.Bytes)

-- | Transfers the data from the t'GI.GLib.Structs.ByteArray.ByteArray' into a new immutable t'GI.GLib.Structs.Bytes.Bytes'.
-- 
-- The t'GI.GLib.Structs.ByteArray.ByteArray' is freed unless the reference count of /@array@/ is greater
-- than one, the t'GI.GLib.Structs.ByteArray.ByteArray' wrapper is preserved but the size of /@array@/
-- will be set to zero.
-- 
-- This is identical to using 'GI.GLib.Structs.Bytes.bytesNewTake' and 'GI.GLib.Functions.byteArrayFree'
-- together.
-- 
-- /Since: 2.32/
byteArrayFreeToBytes ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteString
    -- ^ /@array@/: a t'GI.GLib.Structs.ByteArray.ByteArray'
    -> m GLib.Bytes.Bytes
    -- ^ __Returns:__ a new immutable t'GI.GLib.Structs.Bytes.Bytes' representing same
    --     byte data that was in the array
byteArrayFreeToBytes :: ByteString -> m Bytes
byteArrayFreeToBytes array :: ByteString
array = 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 GByteArray
array' <- ByteString -> IO (Ptr GByteArray)
packGByteArray ByteString
array
    Ptr Bytes
result <- Ptr GByteArray -> IO (Ptr Bytes)
g_byte_array_free_to_bytes Ptr GByteArray
array'
    Text -> Ptr Bytes -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "byteArrayFreeToBytes" Ptr Bytes
result
    Bytes
result' <- ((ManagedPtr Bytes -> Bytes) -> Ptr Bytes -> IO Bytes
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Bytes -> Bytes
GLib.Bytes.Bytes) Ptr Bytes
result
    Bytes -> IO Bytes
forall (m :: * -> *) a. Monad m => a -> m a
return Bytes
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method ByteArray::new
-- method type : MemberFunction
-- Args: []
-- Lengths: []
-- returnType: Just TByteArray
-- throws : False
-- Skip return : False

foreign import ccall "g_byte_array_new" g_byte_array_new :: 
    IO (Ptr GByteArray)

-- | Creates a new t'GI.GLib.Structs.ByteArray.ByteArray' with a reference count of 1.
byteArrayNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m ByteString
    -- ^ __Returns:__ the new t'GI.GLib.Structs.ByteArray.ByteArray'
byteArrayNew :: m ByteString
byteArrayNew  = 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 GByteArray
result <- IO (Ptr GByteArray)
g_byte_array_new
    Text -> Ptr GByteArray -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "byteArrayNew" Ptr GByteArray
result
    ByteString
result' <- Ptr GByteArray -> IO ByteString
unpackGByteArray Ptr GByteArray
result
    Ptr GByteArray -> IO ()
unrefGByteArray Ptr GByteArray
result
    ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method ByteArray::new_take
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "data"
--           , argType = TCArray False (-1) 1 (TBasicType TUInt8)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "byte data for the array"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "len"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "length of @data" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "len"
--              , argType = TBasicType TUInt64
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "length of @data" , sinceVersion = Nothing }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Just TByteArray
-- throws : False
-- Skip return : False

foreign import ccall "g_byte_array_new_take" g_byte_array_new_take :: 
    Ptr Word8 ->                            -- data : TCArray False (-1) 1 (TBasicType TUInt8)
    Word64 ->                               -- len : TBasicType TUInt64
    IO (Ptr GByteArray)

-- | Create byte array containing the data. The data will be owned by the array
-- and will be freed with 'GI.GLib.Functions.free', i.e. it could be allocated using 'GI.GLib.Functions.strdup'.
-- 
-- /Since: 2.32/
byteArrayNewTake ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteString
    -- ^ /@data@/: byte data for the array
    -> m ByteString
    -- ^ __Returns:__ a new t'GI.GLib.Structs.ByteArray.ByteArray'
byteArrayNewTake :: ByteString -> m ByteString
byteArrayNewTake data_ :: ByteString
data_ = 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
    let len :: Word64
len = 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
data_
    Ptr Word8
data_' <- ByteString -> IO (Ptr Word8)
packByteString ByteString
data_
    Ptr GByteArray
result <- Ptr Word8 -> Word64 -> IO (Ptr GByteArray)
g_byte_array_new_take Ptr Word8
data_' Word64
len
    Text -> Ptr GByteArray -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "byteArrayNewTake" Ptr GByteArray
result
    ByteString
result' <- Ptr GByteArray -> IO ByteString
unpackGByteArray Ptr GByteArray
result
    Ptr GByteArray -> IO ()
unrefGByteArray Ptr GByteArray
result
    ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method ByteArray::unref
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "array"
--           , argType = TByteArray
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GByteArray" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_byte_array_unref" g_byte_array_unref :: 
    Ptr GByteArray ->                       -- array : TByteArray
    IO ()

-- | Atomically decrements the reference count of /@array@/ by one. If the
-- reference count drops to 0, all memory allocated by the array is
-- released. This function is thread-safe and may be called from any
-- thread.
-- 
-- /Since: 2.22/
byteArrayUnref ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteString
    -- ^ /@array@/: A t'GI.GLib.Structs.ByteArray.ByteArray'
    -> m ()
byteArrayUnref :: ByteString -> m ()
byteArrayUnref array :: ByteString
array = 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 GByteArray
array' <- ByteString -> IO (Ptr GByteArray)
packGByteArray ByteString
array
    Ptr GByteArray -> IO ()
g_byte_array_unref Ptr GByteArray
array'
    Ptr GByteArray -> IO ()
unrefGByteArray Ptr GByteArray
array'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveByteArrayMethod (t :: Symbol) (o :: *) :: * where
    ResolveByteArrayMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveByteArrayMethod t ByteArray, O.MethodInfo info ByteArray p) => OL.IsLabel t (ByteArray -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif