{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Gio.Objects.BytesIcon.BytesIcon' specifies an image held in memory in a common format (usually
-- png) to be used as icon.
-- 
-- /Since: 2.38/

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

module GI.Gio.Objects.BytesIcon
    ( 

-- * Exported types
    BytesIcon(..)                           ,
    IsBytesIcon                             ,
    toBytesIcon                             ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [equal]("GI.Gio.Interfaces.Icon#g:method:equal"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [load]("GI.Gio.Interfaces.LoadableIcon#g:method:load"), [loadAsync]("GI.Gio.Interfaces.LoadableIcon#g:method:loadAsync"), [loadFinish]("GI.Gio.Interfaces.LoadableIcon#g:method:loadFinish"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [serialize]("GI.Gio.Interfaces.Icon#g:method:serialize"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [toString]("GI.Gio.Interfaces.Icon#g:method:toString"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getBytes]("GI.Gio.Objects.BytesIcon#g:method:getBytes"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveBytesIconMethod                  ,
#endif

-- ** getBytes #method:getBytes#

#if defined(ENABLE_OVERLOADING)
    BytesIconGetBytesMethodInfo             ,
#endif
    bytesIconGetBytes                       ,


-- ** new #method:new#

    bytesIconNew                            ,




 -- * Properties


-- ** bytes #attr:bytes#
-- | The bytes containing the icon.

#if defined(ENABLE_OVERLOADING)
    BytesIconBytesPropertyInfo              ,
#endif
#if defined(ENABLE_OVERLOADING)
    bytesIconBytes                          ,
#endif
    constructBytesIconBytes                 ,
    getBytesIconBytes                       ,




    ) 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

import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gio.Interfaces.Icon as Gio.Icon
import {-# SOURCE #-} qualified GI.Gio.Interfaces.LoadableIcon as Gio.LoadableIcon

-- | Memory-managed wrapper type.
newtype BytesIcon = BytesIcon (SP.ManagedPtr BytesIcon)
    deriving (BytesIcon -> BytesIcon -> Bool
(BytesIcon -> BytesIcon -> Bool)
-> (BytesIcon -> BytesIcon -> Bool) -> Eq BytesIcon
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BytesIcon -> BytesIcon -> Bool
$c/= :: BytesIcon -> BytesIcon -> Bool
== :: BytesIcon -> BytesIcon -> Bool
$c== :: BytesIcon -> BytesIcon -> Bool
Eq)

instance SP.ManagedPtrNewtype BytesIcon where
    toManagedPtr :: BytesIcon -> ManagedPtr BytesIcon
toManagedPtr (BytesIcon ManagedPtr BytesIcon
p) = ManagedPtr BytesIcon
p

foreign import ccall "g_bytes_icon_get_type"
    c_g_bytes_icon_get_type :: IO B.Types.GType

instance B.Types.TypedObject BytesIcon where
    glibType :: IO GType
glibType = IO GType
c_g_bytes_icon_get_type

instance B.Types.GObject BytesIcon

-- | Type class for types which can be safely cast to `BytesIcon`, for instance with `toBytesIcon`.
class (SP.GObject o, O.IsDescendantOf BytesIcon o) => IsBytesIcon o
instance (SP.GObject o, O.IsDescendantOf BytesIcon o) => IsBytesIcon o

instance O.HasParentTypes BytesIcon
type instance O.ParentTypes BytesIcon = '[GObject.Object.Object, Gio.Icon.Icon, Gio.LoadableIcon.LoadableIcon]

-- | Cast to `BytesIcon`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toBytesIcon :: (MIO.MonadIO m, IsBytesIcon o) => o -> m BytesIcon
toBytesIcon :: forall (m :: * -> *) o.
(MonadIO m, IsBytesIcon o) =>
o -> m BytesIcon
toBytesIcon = IO BytesIcon -> m BytesIcon
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO BytesIcon -> m BytesIcon)
-> (o -> IO BytesIcon) -> o -> m BytesIcon
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr BytesIcon -> BytesIcon) -> o -> IO BytesIcon
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr BytesIcon -> BytesIcon
BytesIcon

-- | Convert 'BytesIcon' 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 BytesIcon) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_g_bytes_icon_get_type
    gvalueSet_ :: Ptr GValue -> Maybe BytesIcon -> IO ()
gvalueSet_ Ptr GValue
gv Maybe BytesIcon
P.Nothing = Ptr GValue -> Ptr BytesIcon -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr BytesIcon
forall a. Ptr a
FP.nullPtr :: FP.Ptr BytesIcon)
    gvalueSet_ Ptr GValue
gv (P.Just BytesIcon
obj) = BytesIcon -> (Ptr BytesIcon -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr BytesIcon
obj (Ptr GValue -> Ptr BytesIcon -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe BytesIcon)
gvalueGet_ Ptr GValue
gv = do
        Ptr BytesIcon
ptr <- Ptr GValue -> IO (Ptr BytesIcon)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr BytesIcon)
        if Ptr BytesIcon
ptr Ptr BytesIcon -> Ptr BytesIcon -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr BytesIcon
forall a. Ptr a
FP.nullPtr
        then BytesIcon -> Maybe BytesIcon
forall a. a -> Maybe a
P.Just (BytesIcon -> Maybe BytesIcon)
-> IO BytesIcon -> IO (Maybe BytesIcon)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr BytesIcon -> BytesIcon)
-> Ptr BytesIcon -> IO BytesIcon
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr BytesIcon -> BytesIcon
BytesIcon Ptr BytesIcon
ptr
        else Maybe BytesIcon -> IO (Maybe BytesIcon)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe BytesIcon
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveBytesIconMethod (t :: Symbol) (o :: *) :: * where
    ResolveBytesIconMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveBytesIconMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveBytesIconMethod "equal" o = Gio.Icon.IconEqualMethodInfo
    ResolveBytesIconMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveBytesIconMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveBytesIconMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveBytesIconMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveBytesIconMethod "load" o = Gio.LoadableIcon.LoadableIconLoadMethodInfo
    ResolveBytesIconMethod "loadAsync" o = Gio.LoadableIcon.LoadableIconLoadAsyncMethodInfo
    ResolveBytesIconMethod "loadFinish" o = Gio.LoadableIcon.LoadableIconLoadFinishMethodInfo
    ResolveBytesIconMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveBytesIconMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveBytesIconMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveBytesIconMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveBytesIconMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveBytesIconMethod "serialize" o = Gio.Icon.IconSerializeMethodInfo
    ResolveBytesIconMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveBytesIconMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveBytesIconMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveBytesIconMethod "toString" o = Gio.Icon.IconToStringMethodInfo
    ResolveBytesIconMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveBytesIconMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveBytesIconMethod "getBytes" o = BytesIconGetBytesMethodInfo
    ResolveBytesIconMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveBytesIconMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveBytesIconMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveBytesIconMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveBytesIconMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveBytesIconMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveBytesIconMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveBytesIconMethod t BytesIcon, O.OverloadedMethod info BytesIcon p) => OL.IsLabel t (BytesIcon -> 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 ~ ResolveBytesIconMethod t BytesIcon, O.OverloadedMethod info BytesIcon p, R.HasField t BytesIcon p) => R.HasField t BytesIcon p where
    getField = O.overloadedMethod @info

#endif

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

#endif

-- VVV Prop "bytes"
   -- Type: TInterface (Name {namespace = "GLib", name = "Bytes"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@bytes@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' bytesIcon #bytes
-- @
getBytesIconBytes :: (MonadIO m, IsBytesIcon o) => o -> m GLib.Bytes.Bytes
getBytesIconBytes :: forall (m :: * -> *) o. (MonadIO m, IsBytesIcon o) => o -> m Bytes
getBytesIconBytes o
obj = IO Bytes -> m Bytes
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bytes -> m Bytes) -> IO Bytes -> m Bytes
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Bytes) -> IO Bytes
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getBytesIconBytes" (IO (Maybe Bytes) -> IO Bytes) -> IO (Maybe Bytes) -> IO Bytes
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr Bytes -> Bytes) -> IO (Maybe Bytes)
forall a b.
(GObject a, GBoxed b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyBoxed o
obj String
"bytes" ManagedPtr Bytes -> Bytes
GLib.Bytes.Bytes

-- | Construct a `GValueConstruct` with valid value for the “@bytes@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructBytesIconBytes :: (IsBytesIcon o, MIO.MonadIO m) => GLib.Bytes.Bytes -> m (GValueConstruct o)
constructBytesIconBytes :: forall o (m :: * -> *).
(IsBytesIcon o, MonadIO m) =>
Bytes -> m (GValueConstruct o)
constructBytesIconBytes Bytes
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Bytes -> IO (GValueConstruct o)
forall a o. GBoxed a => String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBoxed String
"bytes" (Bytes -> Maybe Bytes
forall a. a -> Maybe a
P.Just Bytes
val)

#if defined(ENABLE_OVERLOADING)
data BytesIconBytesPropertyInfo
instance AttrInfo BytesIconBytesPropertyInfo where
    type AttrAllowedOps BytesIconBytesPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint BytesIconBytesPropertyInfo = IsBytesIcon
    type AttrSetTypeConstraint BytesIconBytesPropertyInfo = (~) GLib.Bytes.Bytes
    type AttrTransferTypeConstraint BytesIconBytesPropertyInfo = (~) GLib.Bytes.Bytes
    type AttrTransferType BytesIconBytesPropertyInfo = GLib.Bytes.Bytes
    type AttrGetType BytesIconBytesPropertyInfo = GLib.Bytes.Bytes
    type AttrLabel BytesIconBytesPropertyInfo = "bytes"
    type AttrOrigin BytesIconBytesPropertyInfo = BytesIcon
    attrGet = getBytesIconBytes
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructBytesIconBytes
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.BytesIcon.bytes"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-BytesIcon.html#g:attr:bytes"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList BytesIcon
type instance O.AttributeList BytesIcon = BytesIconAttributeList
type BytesIconAttributeList = ('[ '("bytes", BytesIconBytesPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
bytesIconBytes :: AttrLabelProxy "bytes"
bytesIconBytes = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList BytesIcon = BytesIconSignalList
type BytesIconSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

-- method BytesIcon::new
-- method type : Constructor
-- 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 = "Gio" , name = "BytesIcon" })
-- throws : False
-- Skip return : False

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

-- | Creates a new icon for a bytes.
-- 
-- This cannot fail, but loading and interpreting the bytes may fail later on
-- (for example, if 'GI.Gio.Interfaces.LoadableIcon.loadableIconLoad' is called) if the image is invalid.
-- 
-- /Since: 2.38/
bytesIconNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GLib.Bytes.Bytes
    -- ^ /@bytes@/: a t'GI.GLib.Structs.Bytes.Bytes'.
    -> m BytesIcon
    -- ^ __Returns:__ a t'GI.Gio.Interfaces.Icon.Icon' for the given
    --   /@bytes@/.
bytesIconNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Bytes -> m BytesIcon
bytesIconNew Bytes
bytes = IO BytesIcon -> m BytesIcon
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO BytesIcon -> m BytesIcon) -> IO BytesIcon -> m BytesIcon
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 BytesIcon
result <- Ptr Bytes -> IO (Ptr BytesIcon)
g_bytes_icon_new Ptr Bytes
bytes'
    Text -> Ptr BytesIcon -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"bytesIconNew" Ptr BytesIcon
result
    BytesIcon
result' <- ((ManagedPtr BytesIcon -> BytesIcon)
-> Ptr BytesIcon -> IO BytesIcon
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr BytesIcon -> BytesIcon
BytesIcon) Ptr BytesIcon
result
    Bytes -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bytes
bytes
    BytesIcon -> IO BytesIcon
forall (m :: * -> *) a. Monad m => a -> m a
return BytesIcon
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method BytesIcon::get_bytes
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "icon"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "BytesIcon" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GIcon." , 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_icon_get_bytes" g_bytes_icon_get_bytes :: 
    Ptr BytesIcon ->                        -- icon : TInterface (Name {namespace = "Gio", name = "BytesIcon"})
    IO (Ptr GLib.Bytes.Bytes)

-- | Gets the t'GI.GLib.Structs.Bytes.Bytes' associated with the given /@icon@/.
-- 
-- /Since: 2.38/
bytesIconGetBytes ::
    (B.CallStack.HasCallStack, MonadIO m, IsBytesIcon a) =>
    a
    -- ^ /@icon@/: a t'GI.Gio.Interfaces.Icon.Icon'.
    -> m GLib.Bytes.Bytes
    -- ^ __Returns:__ a t'GI.GLib.Structs.Bytes.Bytes'.
bytesIconGetBytes :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBytesIcon a) =>
a -> m Bytes
bytesIconGetBytes a
icon = 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 BytesIcon
icon' <- a -> IO (Ptr BytesIcon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
icon
    Ptr Bytes
result <- Ptr BytesIcon -> IO (Ptr Bytes)
g_bytes_icon_get_bytes Ptr BytesIcon
icon'
    Text -> Ptr Bytes -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"bytesIconGetBytes" Ptr Bytes
result
    Bytes
result' <- ((ManagedPtr Bytes -> Bytes) -> Ptr Bytes -> IO Bytes
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Bytes -> Bytes
GLib.Bytes.Bytes) Ptr Bytes
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
icon
    Bytes -> IO Bytes
forall (m :: * -> *) a. Monad m => a -> m a
return Bytes
result'

#if defined(ENABLE_OVERLOADING)
data BytesIconGetBytesMethodInfo
instance (signature ~ (m GLib.Bytes.Bytes), MonadIO m, IsBytesIcon a) => O.OverloadedMethod BytesIconGetBytesMethodInfo a signature where
    overloadedMethod = bytesIconGetBytes

instance O.OverloadedMethodInfo BytesIconGetBytesMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.BytesIcon.bytesIconGetBytes",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-BytesIcon.html#v:bytesIconGetBytes"
        })


#endif