{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A simple refcounted data type representing an immutable sequence of zero or
-- more bytes from an unspecified origin.
-- 
-- The purpose of a t'GI.GLib.Structs.Bytes.Bytes' is to keep the memory region that it holds
-- alive for as long as anyone holds a reference to the bytes.  When
-- the last reference count is dropped, the memory is released. Multiple
-- unrelated callers can use byte data in the t'GI.GLib.Structs.Bytes.Bytes' without coordinating
-- their activities, resting assured that the byte data will not change or
-- move while they hold a reference.
-- 
-- A t'GI.GLib.Structs.Bytes.Bytes' can come from many different origins that may have
-- different procedures for freeing the memory region.  Examples are
-- memory from 'GI.GLib.Functions.malloc', from memory slices, from a t'GI.GLib.Structs.MappedFile.MappedFile' or
-- memory from other allocators.
-- 
-- t'GI.GLib.Structs.Bytes.Bytes' work well as keys in t'GI.GLib.Structs.HashTable.HashTable'. Use 'GI.GLib.Structs.Bytes.bytesEqual' and
-- 'GI.GLib.Structs.Bytes.bytesHash' as parameters to @/g_hash_table_new()/@ or @/g_hash_table_new_full()/@.
-- t'GI.GLib.Structs.Bytes.Bytes' can also be used as keys in a t'GI.GLib.Structs.Tree.Tree' by passing the 'GI.GLib.Structs.Bytes.bytesCompare'
-- function to @/g_tree_new()/@.
-- 
-- The data pointed to by this bytes must not be modified. For a mutable
-- array of bytes see t'GI.GLib.Structs.ByteArray.ByteArray'. Use 'GI.GLib.Structs.Bytes.bytesUnrefToArray' to create a
-- mutable array for a t'GI.GLib.Structs.Bytes.Bytes' sequence. To create an immutable t'GI.GLib.Structs.Bytes.Bytes' from
-- a mutable t'GI.GLib.Structs.ByteArray.ByteArray', use the 'GI.GLib.Functions.byteArrayFreeToBytes' function.
-- 
-- /Since: 2.32/

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

module GI.GLib.Structs.Bytes
    ( 

-- * Exported types
    Bytes(..)                               ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [compare]("GI.GLib.Structs.Bytes#g:method:compare"), [equal]("GI.GLib.Structs.Bytes#g:method:equal"), [hash]("GI.GLib.Structs.Bytes#g:method:hash"), [newFromBytes]("GI.GLib.Structs.Bytes#g:method:newFromBytes"), [ref]("GI.GLib.Structs.Bytes#g:method:ref"), [unref]("GI.GLib.Structs.Bytes#g:method:unref"), [unrefToArray]("GI.GLib.Structs.Bytes#g:method:unrefToArray"), [unrefToData]("GI.GLib.Structs.Bytes#g:method:unrefToData").
-- 
-- ==== Getters
-- [getData]("GI.GLib.Structs.Bytes#g:method:getData"), [getRegion]("GI.GLib.Structs.Bytes#g:method:getRegion"), [getSize]("GI.GLib.Structs.Bytes#g:method:getSize").
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolveBytesMethod                      ,
#endif

-- ** compare #method:compare#

#if defined(ENABLE_OVERLOADING)
    BytesCompareMethodInfo                  ,
#endif
    bytesCompare                            ,


-- ** equal #method:equal#

#if defined(ENABLE_OVERLOADING)
    BytesEqualMethodInfo                    ,
#endif
    bytesEqual                              ,


-- ** getData #method:getData#

#if defined(ENABLE_OVERLOADING)
    BytesGetDataMethodInfo                  ,
#endif
    bytesGetData                            ,


-- ** getRegion #method:getRegion#

#if defined(ENABLE_OVERLOADING)
    BytesGetRegionMethodInfo                ,
#endif
    bytesGetRegion                          ,


-- ** getSize #method:getSize#

#if defined(ENABLE_OVERLOADING)
    BytesGetSizeMethodInfo                  ,
#endif
    bytesGetSize                            ,


-- ** hash #method:hash#

#if defined(ENABLE_OVERLOADING)
    BytesHashMethodInfo                     ,
#endif
    bytesHash                               ,


-- ** new #method:new#

    bytesNew                                ,


-- ** newFromBytes #method:newFromBytes#

#if defined(ENABLE_OVERLOADING)
    BytesNewFromBytesMethodInfo             ,
#endif
    bytesNewFromBytes                       ,


-- ** newTake #method:newTake#

    bytesNewTake                            ,


-- ** ref #method:ref#

#if defined(ENABLE_OVERLOADING)
    BytesRefMethodInfo                      ,
#endif
    bytesRef                                ,


-- ** unref #method:unref#

#if defined(ENABLE_OVERLOADING)
    BytesUnrefMethodInfo                    ,
#endif
    bytesUnref                              ,


-- ** unrefToArray #method:unrefToArray#

#if defined(ENABLE_OVERLOADING)
    BytesUnrefToArrayMethodInfo             ,
#endif
    bytesUnrefToArray                       ,


-- ** unrefToData #method:unrefToData#

#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.GArray as B.GArray
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.Coerce as Coerce
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 qualified GHC.Records as R


-- | Memory-managed wrapper type.
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

-- | Convert 'Bytes' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe Bytes) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_g_bytes_get_type
    gvalueSet_ :: Ptr GValue -> Maybe Bytes -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Bytes
P.Nothing = Ptr GValue -> Ptr Bytes -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr Bytes
forall a. Ptr a
FP.nullPtr :: FP.Ptr Bytes)
    gvalueSet_ Ptr GValue
gv (P.Just Bytes
obj) = Bytes -> (Ptr Bytes -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Bytes
obj (Ptr GValue -> Ptr Bytes -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe Bytes)
gvalueGet_ Ptr GValue
gv = do
        Ptr Bytes
ptr <- Ptr GValue -> IO (Ptr Bytes)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr Bytes)
        if Ptr Bytes
ptr Ptr Bytes -> Ptr Bytes -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Bytes
forall a. Ptr a
FP.nullPtr
        then Bytes -> Maybe Bytes
forall a. a -> Maybe a
P.Just (Bytes -> Maybe Bytes) -> IO Bytes -> IO (Maybe Bytes)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (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
        else Maybe Bytes -> IO (Maybe Bytes)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Bytes
forall a. Maybe a
P.Nothing
        
    


#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Bytes
type instance O.AttributeList Bytes = BytesAttributeList
type BytesAttributeList = ('[ ] :: [(Symbol, *)])
#endif

-- method Bytes::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "data"
--           , argType = TCArray False (-1) 1 (TBasicType TUInt8)
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "\n       the data to be used for the bytes"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the size of @data" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "size"
--              , argType = TBasicType TUInt64
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "the size of @data" , sinceVersion = Nothing }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "Bytes" })
-- throws : False
-- Skip return : False

foreign import ccall "g_bytes_new" g_bytes_new :: 
    Ptr Word8 ->                            -- data : TCArray False (-1) 1 (TBasicType TUInt8)
    Word64 ->                               -- size : TBasicType TUInt64
    IO (Ptr Bytes)

-- | Creates a new t'GI.GLib.Structs.Bytes.Bytes' from /@data@/.
-- 
-- /@data@/ is copied. If /@size@/ is 0, /@data@/ may be 'P.Nothing'.
-- 
-- /Since: 2.32/
bytesNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Maybe (ByteString)
    -- ^ /@data@/: 
    --        the data to be used for the bytes
    -> m Bytes
    -- ^ __Returns:__ a new t'GI.GLib.Structs.Bytes.Bytes'
bytesNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
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

-- method Bytes::new_take
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "data"
--           , argType = TCArray False (-1) 1 (TBasicType TUInt8)
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "\n       the data to be used for the bytes"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the size of @data" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "size"
--              , argType = TBasicType TUInt64
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "the size of @data" , sinceVersion = Nothing }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "Bytes" })
-- throws : False
-- Skip return : False

foreign import ccall "g_bytes_new_take" g_bytes_new_take :: 
    Ptr Word8 ->                            -- data : TCArray False (-1) 1 (TBasicType TUInt8)
    Word64 ->                               -- size : TBasicType TUInt64
    IO (Ptr Bytes)

-- | Creates a new t'GI.GLib.Structs.Bytes.Bytes' from /@data@/.
-- 
-- After this call, /@data@/ belongs to the bytes and may no longer be
-- modified by the caller.  'GI.GLib.Functions.free' will be called on /@data@/ when the
-- bytes is no longer in use. Because of this /@data@/ must have been created by
-- a call to 'GI.GLib.Functions.malloc', 'GI.GLib.Functions.malloc0' or 'GI.GLib.Functions.realloc' or by one of the many
-- functions that wrap these calls (such as @/g_new()/@, 'GI.GLib.Functions.strdup', etc).
-- 
-- For creating t'GI.GLib.Structs.Bytes.Bytes' with memory from other allocators, see
-- @/g_bytes_new_with_free_func()/@.
-- 
-- /@data@/ may be 'P.Nothing' if /@size@/ is 0.
-- 
-- /Since: 2.32/
bytesNewTake ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Maybe (ByteString)
    -- ^ /@data@/: 
    --        the data to be used for the bytes
    -> m Bytes
    -- ^ __Returns:__ a new t'GI.GLib.Structs.Bytes.Bytes'
bytesNewTake :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
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

-- method Bytes::compare
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bytes1"
--           , argType = TInterface Name { namespace = "GLib" , name = "Bytes" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a pointer to a #GBytes"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "bytes2"
--           , argType = TInterface Name { namespace = "GLib" , name = "Bytes" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a pointer to a #GBytes to compare with @bytes1"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "g_bytes_compare" g_bytes_compare :: 
    Ptr Bytes ->                            -- bytes1 : TInterface (Name {namespace = "GLib", name = "Bytes"})
    Ptr Bytes ->                            -- bytes2 : TInterface (Name {namespace = "GLib", name = "Bytes"})
    IO Int32

-- | Compares the two t'GI.GLib.Structs.Bytes.Bytes' values.
-- 
-- This function can be used to sort GBytes instances in lexicographical order.
-- 
-- If /@bytes1@/ and /@bytes2@/ have different length but the shorter one is a
-- prefix of the longer one then the shorter one is considered to be less than
-- the longer one. Otherwise the first byte where both differ is used for
-- comparison. If /@bytes1@/ has a smaller value at that position it is
-- considered less, otherwise greater than /@bytes2@/.
-- 
-- /Since: 2.32/
bytesCompare ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bytes
    -- ^ /@bytes1@/: a pointer to a t'GI.GLib.Structs.Bytes.Bytes'
    -> Bytes
    -- ^ /@bytes2@/: a pointer to a t'GI.GLib.Structs.Bytes.Bytes' to compare with /@bytes1@/
    -> m Int32
    -- ^ __Returns:__ a negative value if /@bytes1@/ is less than /@bytes2@/, a positive value
    --          if /@bytes1@/ is greater than /@bytes2@/, and zero if /@bytes1@/ is equal to
    --          /@bytes2@/
bytesCompare :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
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.OverloadedMethod BytesCompareMethodInfo Bytes signature where
    overloadedMethod = bytesCompare

instance O.OverloadedMethodInfo BytesCompareMethodInfo Bytes where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Bytes.bytesCompare",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Bytes.html#v:bytesCompare"
        })


#endif

-- method Bytes::equal
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bytes1"
--           , argType = TInterface Name { namespace = "GLib" , name = "Bytes" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a pointer to a #GBytes"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "bytes2"
--           , argType = TInterface Name { namespace = "GLib" , name = "Bytes" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a pointer to a #GBytes to compare with @bytes1"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_bytes_equal" g_bytes_equal :: 
    Ptr Bytes ->                            -- bytes1 : TInterface (Name {namespace = "GLib", name = "Bytes"})
    Ptr Bytes ->                            -- bytes2 : TInterface (Name {namespace = "GLib", name = "Bytes"})
    IO CInt

-- | Compares the two t'GI.GLib.Structs.Bytes.Bytes' values being pointed to and returns
-- 'P.True' if they are equal.
-- 
-- This function can be passed to @/g_hash_table_new()/@ as the /@keyEqualFunc@/
-- parameter, when using non-'P.Nothing' t'GI.GLib.Structs.Bytes.Bytes' pointers as keys in a t'GI.GLib.Structs.HashTable.HashTable'.
-- 
-- /Since: 2.32/
bytesEqual ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bytes
    -- ^ /@bytes1@/: a pointer to a t'GI.GLib.Structs.Bytes.Bytes'
    -> Bytes
    -- ^ /@bytes2@/: a pointer to a t'GI.GLib.Structs.Bytes.Bytes' to compare with /@bytes1@/
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the two keys match.
bytesEqual :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
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.OverloadedMethod BytesEqualMethodInfo Bytes signature where
    overloadedMethod = bytesEqual

instance O.OverloadedMethodInfo BytesEqualMethodInfo Bytes where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Bytes.bytesEqual",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Bytes.html#v:bytesEqual"
        })


#endif

-- method Bytes::get_data
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bytes"
--           , argType = TInterface Name { namespace = "GLib" , name = "Bytes" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBytes" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TUInt64
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "location to return size of byte data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "size"
--              , argType = TBasicType TUInt64
--              , direction = DirectionOut
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "location to return size of byte data"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferEverything
--              }
--          ]
-- returnType: Just (TCArray False (-1) 1 (TBasicType TUInt8))
-- throws : False
-- Skip return : False

foreign import ccall "g_bytes_get_data" g_bytes_get_data :: 
    Ptr Bytes ->                            -- bytes : TInterface (Name {namespace = "GLib", name = "Bytes"})
    Ptr Word64 ->                           -- size : TBasicType TUInt64
    IO (Ptr Word8)

-- | Get the byte data in the t'GI.GLib.Structs.Bytes.Bytes'. This data should not be modified.
-- 
-- This function will always return the same pointer for a given t'GI.GLib.Structs.Bytes.Bytes'.
-- 
-- 'P.Nothing' may be returned if /@size@/ is 0. This is not guaranteed, as the t'GI.GLib.Structs.Bytes.Bytes'
-- may represent an empty string with /@data@/ non-'P.Nothing' and /@size@/ as 0. 'P.Nothing' will
-- not be returned if /@size@/ is non-zero.
-- 
-- /Since: 2.32/
bytesGetData ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bytes
    -- ^ /@bytes@/: a t'GI.GLib.Structs.Bytes.Bytes'
    -> m (Maybe ByteString)
    -- ^ __Returns:__ 
    --          a pointer to the byte data, or 'P.Nothing'
bytesGetData :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
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.OverloadedMethod BytesGetDataMethodInfo Bytes signature where
    overloadedMethod = bytesGetData

instance O.OverloadedMethodInfo BytesGetDataMethodInfo Bytes where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Bytes.bytesGetData",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Bytes.html#v:bytesGetData"
        })


#endif

-- method Bytes::get_region
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bytes"
--           , argType = TInterface Name { namespace = "GLib" , name = "Bytes" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBytes" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "element_size"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a non-zero element size"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "offset"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "an offset to the start of the region within the @bytes"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_elements"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the number of elements in the region"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TPtr)
-- throws : False
-- Skip return : False

foreign import ccall "g_bytes_get_region" g_bytes_get_region :: 
    Ptr Bytes ->                            -- bytes : TInterface (Name {namespace = "GLib", name = "Bytes"})
    Word64 ->                               -- element_size : TBasicType TUInt64
    Word64 ->                               -- offset : TBasicType TUInt64
    Word64 ->                               -- n_elements : TBasicType TUInt64
    IO (Ptr ())

-- | Gets a pointer to a region in /@bytes@/.
-- 
-- The region starts at /@offset@/ many bytes from the start of the data
-- and contains /@nElements@/ many elements of /@elementSize@/ size.
-- 
-- /@nElements@/ may be zero, but /@elementSize@/ must always be non-zero.
-- Ideally, /@elementSize@/ is a static constant (eg: sizeof a struct).
-- 
-- This function does careful bounds checking (including checking for
-- arithmetic overflows) and returns a non-'P.Nothing' pointer if the
-- specified region lies entirely within the /@bytes@/. If the region is
-- in some way out of range, or if an overflow has occurred, then 'P.Nothing'
-- is returned.
-- 
-- Note: it is possible to have a valid zero-size region. In this case,
-- the returned pointer will be equal to the base pointer of the data of
-- /@bytes@/, plus /@offset@/.  This will be non-'P.Nothing' except for the case
-- where /@bytes@/ itself was a zero-sized region.  Since it is unlikely
-- that you will be using this function to check for a zero-sized region
-- in a zero-sized /@bytes@/, 'P.Nothing' effectively always means \"error\".
-- 
-- /Since: 2.70/
bytesGetRegion ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bytes
    -- ^ /@bytes@/: a t'GI.GLib.Structs.Bytes.Bytes'
    -> Word64
    -- ^ /@elementSize@/: a non-zero element size
    -> Word64
    -- ^ /@offset@/: an offset to the start of the region within the /@bytes@/
    -> Word64
    -- ^ /@nElements@/: the number of elements in the region
    -> m (Ptr ())
    -- ^ __Returns:__ the requested region, or 'P.Nothing' in case of an error
bytesGetRegion :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Bytes -> Word64 -> Word64 -> Word64 -> m (Ptr ())
bytesGetRegion Bytes
bytes Word64
elementSize Word64
offset Word64
nElements = IO (Ptr ()) -> m (Ptr ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr ()) -> m (Ptr ())) -> IO (Ptr ()) -> m (Ptr ())
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 ()
result <- Ptr Bytes -> Word64 -> Word64 -> Word64 -> IO (Ptr ())
g_bytes_get_region Ptr Bytes
bytes' Word64
elementSize Word64
offset Word64
nElements
    Bytes -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bytes
bytes
    Ptr () -> IO (Ptr ())
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result

#if defined(ENABLE_OVERLOADING)
data BytesGetRegionMethodInfo
instance (signature ~ (Word64 -> Word64 -> Word64 -> m (Ptr ())), MonadIO m) => O.OverloadedMethod BytesGetRegionMethodInfo Bytes signature where
    overloadedMethod = bytesGetRegion

instance O.OverloadedMethodInfo BytesGetRegionMethodInfo Bytes where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Bytes.bytesGetRegion",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Bytes.html#v:bytesGetRegion"
        })


#endif

-- method Bytes::get_size
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bytes"
--           , argType = TInterface Name { namespace = "GLib" , name = "Bytes" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBytes" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt64)
-- throws : False
-- Skip return : False

foreign import ccall "g_bytes_get_size" g_bytes_get_size :: 
    Ptr Bytes ->                            -- bytes : TInterface (Name {namespace = "GLib", name = "Bytes"})
    IO Word64

-- | Get the size of the byte data in the t'GI.GLib.Structs.Bytes.Bytes'.
-- 
-- This function will always return the same value for a given t'GI.GLib.Structs.Bytes.Bytes'.
-- 
-- /Since: 2.32/
bytesGetSize ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bytes
    -- ^ /@bytes@/: a t'GI.GLib.Structs.Bytes.Bytes'
    -> m Word64
    -- ^ __Returns:__ the size
bytesGetSize :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
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.OverloadedMethod BytesGetSizeMethodInfo Bytes signature where
    overloadedMethod = bytesGetSize

instance O.OverloadedMethodInfo BytesGetSizeMethodInfo Bytes where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Bytes.bytesGetSize",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Bytes.html#v:bytesGetSize"
        })


#endif

-- method Bytes::hash
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bytes"
--           , argType = TInterface Name { namespace = "GLib" , name = "Bytes" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a pointer to a #GBytes key"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "g_bytes_hash" g_bytes_hash :: 
    Ptr Bytes ->                            -- bytes : TInterface (Name {namespace = "GLib", name = "Bytes"})
    IO Word32

-- | Creates an integer hash code for the byte data in the t'GI.GLib.Structs.Bytes.Bytes'.
-- 
-- This function can be passed to @/g_hash_table_new()/@ as the /@keyHashFunc@/
-- parameter, when using non-'P.Nothing' t'GI.GLib.Structs.Bytes.Bytes' pointers as keys in a t'GI.GLib.Structs.HashTable.HashTable'.
-- 
-- /Since: 2.32/
bytesHash ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bytes
    -- ^ /@bytes@/: a pointer to a t'GI.GLib.Structs.Bytes.Bytes' key
    -> m Word32
    -- ^ __Returns:__ a hash value corresponding to the key.
bytesHash :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
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.OverloadedMethod BytesHashMethodInfo Bytes signature where
    overloadedMethod = bytesHash

instance O.OverloadedMethodInfo BytesHashMethodInfo Bytes where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Bytes.bytesHash",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Bytes.html#v:bytesHash"
        })


#endif

-- method Bytes::new_from_bytes
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bytes"
--           , argType = TInterface Name { namespace = "GLib" , name = "Bytes" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBytes" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "offset"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "offset which subsection starts at"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "length"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "length of subsection"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "Bytes" })
-- throws : False
-- Skip return : False

foreign import ccall "g_bytes_new_from_bytes" g_bytes_new_from_bytes :: 
    Ptr Bytes ->                            -- bytes : TInterface (Name {namespace = "GLib", name = "Bytes"})
    Word64 ->                               -- offset : TBasicType TUInt64
    Word64 ->                               -- length : TBasicType TUInt64
    IO (Ptr Bytes)

-- | Creates a t'GI.GLib.Structs.Bytes.Bytes' which is a subsection of another t'GI.GLib.Structs.Bytes.Bytes'. The /@offset@/ +
-- /@length@/ may not be longer than the size of /@bytes@/.
-- 
-- A reference to /@bytes@/ will be held by the newly created t'GI.GLib.Structs.Bytes.Bytes' until
-- the byte data is no longer needed.
-- 
-- Since 2.56, if /@offset@/ is 0 and /@length@/ matches the size of /@bytes@/, then
-- /@bytes@/ will be returned with the reference count incremented by 1. If /@bytes@/
-- is a slice of another t'GI.GLib.Structs.Bytes.Bytes', then the resulting t'GI.GLib.Structs.Bytes.Bytes' will reference
-- the same t'GI.GLib.Structs.Bytes.Bytes' instead of /@bytes@/. This allows consumers to simplify the
-- usage of t'GI.GLib.Structs.Bytes.Bytes' when asynchronously writing to streams.
-- 
-- /Since: 2.32/
bytesNewFromBytes ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bytes
    -- ^ /@bytes@/: a t'GI.GLib.Structs.Bytes.Bytes'
    -> Word64
    -- ^ /@offset@/: offset which subsection starts at
    -> Word64
    -- ^ /@length@/: length of subsection
    -> m Bytes
    -- ^ __Returns:__ a new t'GI.GLib.Structs.Bytes.Bytes'
bytesNewFromBytes :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
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.OverloadedMethod BytesNewFromBytesMethodInfo Bytes signature where
    overloadedMethod = bytesNewFromBytes

instance O.OverloadedMethodInfo BytesNewFromBytesMethodInfo Bytes where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Bytes.bytesNewFromBytes",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Bytes.html#v:bytesNewFromBytes"
        })


#endif

-- method Bytes::ref
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bytes"
--           , argType = TInterface Name { namespace = "GLib" , name = "Bytes" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBytes" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "Bytes" })
-- throws : False
-- Skip return : False

foreign import ccall "g_bytes_ref" g_bytes_ref :: 
    Ptr Bytes ->                            -- bytes : TInterface (Name {namespace = "GLib", name = "Bytes"})
    IO (Ptr Bytes)

-- | Increase the reference count on /@bytes@/.
-- 
-- /Since: 2.32/
bytesRef ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bytes
    -- ^ /@bytes@/: a t'GI.GLib.Structs.Bytes.Bytes'
    -> m Bytes
    -- ^ __Returns:__ the t'GI.GLib.Structs.Bytes.Bytes'
bytesRef :: forall (m :: * -> *). (HasCallStack, MonadIO m) => 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.OverloadedMethod BytesRefMethodInfo Bytes signature where
    overloadedMethod = bytesRef

instance O.OverloadedMethodInfo BytesRefMethodInfo Bytes where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Bytes.bytesRef",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Bytes.html#v:bytesRef"
        })


#endif

-- method Bytes::unref
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bytes"
--           , argType = TInterface Name { namespace = "GLib" , name = "Bytes" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBytes" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_bytes_unref" g_bytes_unref :: 
    Ptr Bytes ->                            -- bytes : TInterface (Name {namespace = "GLib", name = "Bytes"})
    IO ()

-- | Releases a reference on /@bytes@/.  This may result in the bytes being
-- freed. If /@bytes@/ is 'P.Nothing', it will return immediately.
-- 
-- /Since: 2.32/
bytesUnref ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bytes
    -- ^ /@bytes@/: a t'GI.GLib.Structs.Bytes.Bytes'
    -> m ()
bytesUnref :: forall (m :: * -> *). (HasCallStack, MonadIO m) => 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.OverloadedMethod BytesUnrefMethodInfo Bytes signature where
    overloadedMethod = bytesUnref

instance O.OverloadedMethodInfo BytesUnrefMethodInfo Bytes where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Bytes.bytesUnref",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Bytes.html#v:bytesUnref"
        })


#endif

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

foreign import ccall "g_bytes_unref_to_array" g_bytes_unref_to_array :: 
    Ptr Bytes ->                            -- bytes : TInterface (Name {namespace = "GLib", name = "Bytes"})
    IO (Ptr GByteArray)

-- | Unreferences the bytes, and returns a new mutable t'GI.GLib.Structs.ByteArray.ByteArray' containing
-- the same byte data.
-- 
-- As an optimization, the byte data is transferred to the array without copying
-- if this was the last reference to bytes and bytes was created with
-- 'GI.GLib.Structs.Bytes.bytesNew', 'GI.GLib.Structs.Bytes.bytesNewTake' or 'GI.GLib.Functions.byteArrayFreeToBytes'. In all
-- other cases the data is copied.
-- 
-- Do not use it if /@bytes@/ contains more than @/G_MAXUINT/@
-- bytes. t'GI.GLib.Structs.ByteArray.ByteArray' stores the length of its data in @/guint/@, which
-- may be shorter than @/gsize/@, that /@bytes@/ is using.
-- 
-- /Since: 2.32/
bytesUnrefToArray ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bytes
    -- ^ /@bytes@/: a t'GI.GLib.Structs.Bytes.Bytes'
    -> m ByteString
    -- ^ __Returns:__ a new mutable t'GI.GLib.Structs.ByteArray.ByteArray' containing the same byte data
bytesUnrefToArray :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
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.OverloadedMethod BytesUnrefToArrayMethodInfo Bytes signature where
    overloadedMethod = bytesUnrefToArray

instance O.OverloadedMethodInfo BytesUnrefToArrayMethodInfo Bytes where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Bytes.bytesUnrefToArray",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Bytes.html#v:bytesUnrefToArray"
        })


#endif

-- method Bytes::unref_to_data
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bytes"
--           , argType = TInterface Name { namespace = "GLib" , name = "Bytes" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBytes" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TUInt64
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "location to place the length of the returned data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "size"
--              , argType = TBasicType TUInt64
--              , direction = DirectionOut
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText =
--                        Just "location to place the length of the returned data"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferEverything
--              }
--          ]
-- returnType: Just (TCArray False (-1) 1 (TBasicType TUInt8))
-- throws : False
-- Skip return : False

foreign import ccall "g_bytes_unref_to_data" g_bytes_unref_to_data :: 
    Ptr Bytes ->                            -- bytes : TInterface (Name {namespace = "GLib", name = "Bytes"})
    Ptr Word64 ->                           -- size : TBasicType TUInt64
    IO (Ptr Word8)

-- | Unreferences the bytes, and returns a pointer the same byte data
-- contents.
-- 
-- As an optimization, the byte data is returned without copying if this was
-- the last reference to bytes and bytes was created with 'GI.GLib.Structs.Bytes.bytesNew',
-- 'GI.GLib.Structs.Bytes.bytesNewTake' or 'GI.GLib.Functions.byteArrayFreeToBytes'. In all other cases the
-- data is copied.
-- 
-- /Since: 2.32/
bytesUnrefToData ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Bytes
    -- ^ /@bytes@/: a t'GI.GLib.Structs.Bytes.Bytes'
    -> m ByteString
    -- ^ __Returns:__ a pointer to the same byte data, which should be
    --          freed with 'GI.GLib.Functions.free'
bytesUnrefToData :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
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.OverloadedMethod BytesUnrefToDataMethodInfo Bytes signature where
    overloadedMethod = bytesUnrefToData

instance O.OverloadedMethodInfo BytesUnrefToDataMethodInfo Bytes where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Bytes.bytesUnrefToData",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Bytes.html#v: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 "getRegion" o = BytesGetRegionMethodInfo
    ResolveBytesMethod "getSize" o = BytesGetSizeMethodInfo
    ResolveBytesMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveBytesMethod t Bytes, O.OverloadedMethod 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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveBytesMethod t Bytes, O.OverloadedMethod info Bytes p, R.HasField t Bytes p) => R.HasField t Bytes p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveBytesMethod t Bytes, O.OverloadedMethodInfo info Bytes) => OL.IsLabel t (O.MethodProxy info Bytes) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif