{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Objects.IconInfo
    ( 
    IconInfo(..)                            ,
    IsIconInfo                              ,
    toIconInfo                              ,
 
#if defined(ENABLE_OVERLOADING)
    ResolveIconInfoMethod                   ,
#endif
#if defined(ENABLE_OVERLOADING)
    IconInfoGetAttachPointsMethodInfo       ,
#endif
    iconInfoGetAttachPoints                 ,
#if defined(ENABLE_OVERLOADING)
    IconInfoGetBaseScaleMethodInfo          ,
#endif
    iconInfoGetBaseScale                    ,
#if defined(ENABLE_OVERLOADING)
    IconInfoGetBaseSizeMethodInfo           ,
#endif
    iconInfoGetBaseSize                     ,
#if defined(ENABLE_OVERLOADING)
    IconInfoGetBuiltinPixbufMethodInfo      ,
#endif
    iconInfoGetBuiltinPixbuf                ,
#if defined(ENABLE_OVERLOADING)
    IconInfoGetDisplayNameMethodInfo        ,
#endif
    iconInfoGetDisplayName                  ,
#if defined(ENABLE_OVERLOADING)
    IconInfoGetEmbeddedRectMethodInfo       ,
#endif
    iconInfoGetEmbeddedRect                 ,
#if defined(ENABLE_OVERLOADING)
    IconInfoGetFilenameMethodInfo           ,
#endif
    iconInfoGetFilename                     ,
#if defined(ENABLE_OVERLOADING)
    IconInfoIsSymbolicMethodInfo            ,
#endif
    iconInfoIsSymbolic                      ,
#if defined(ENABLE_OVERLOADING)
    IconInfoLoadIconMethodInfo              ,
#endif
    iconInfoLoadIcon                        ,
#if defined(ENABLE_OVERLOADING)
    IconInfoLoadIconAsyncMethodInfo         ,
#endif
    iconInfoLoadIconAsync                   ,
#if defined(ENABLE_OVERLOADING)
    IconInfoLoadIconFinishMethodInfo        ,
#endif
    iconInfoLoadIconFinish                  ,
#if defined(ENABLE_OVERLOADING)
    IconInfoLoadSurfaceMethodInfo           ,
#endif
    iconInfoLoadSurface                     ,
#if defined(ENABLE_OVERLOADING)
    IconInfoLoadSymbolicMethodInfo          ,
#endif
    iconInfoLoadSymbolic                    ,
#if defined(ENABLE_OVERLOADING)
    IconInfoLoadSymbolicAsyncMethodInfo     ,
#endif
    iconInfoLoadSymbolicAsync               ,
#if defined(ENABLE_OVERLOADING)
    IconInfoLoadSymbolicFinishMethodInfo    ,
#endif
    iconInfoLoadSymbolicFinish              ,
#if defined(ENABLE_OVERLOADING)
    IconInfoLoadSymbolicForContextMethodInfo,
#endif
    iconInfoLoadSymbolicForContext          ,
#if defined(ENABLE_OVERLOADING)
    IconInfoLoadSymbolicForContextAsyncMethodInfo,
#endif
    iconInfoLoadSymbolicForContextAsync     ,
#if defined(ENABLE_OVERLOADING)
    IconInfoLoadSymbolicForContextFinishMethodInfo,
#endif
    iconInfoLoadSymbolicForContextFinish    ,
#if defined(ENABLE_OVERLOADING)
    IconInfoLoadSymbolicForStyleMethodInfo  ,
#endif
    iconInfoLoadSymbolicForStyle            ,
    iconInfoNewForPixbuf                    ,
#if defined(ENABLE_OVERLOADING)
    IconInfoSetRawCoordinatesMethodInfo     ,
#endif
    iconInfoSetRawCoordinates               ,
    ) 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.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.Cairo.Structs.Surface as Cairo.Surface
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Objects.Window as Gdk.Window
import qualified GI.Gdk.Structs.Point as Gdk.Point
import qualified GI.Gdk.Structs.RGBA as Gdk.RGBA
import qualified GI.Gdk.Structs.Rectangle as Gdk.Rectangle
import qualified GI.GdkPixbuf.Objects.Pixbuf as GdkPixbuf.Pixbuf
import qualified GI.Gio.Callbacks as Gio.Callbacks
import qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Objects.IconTheme as Gtk.IconTheme
import {-# SOURCE #-} qualified GI.Gtk.Objects.Style as Gtk.Style
import {-# SOURCE #-} qualified GI.Gtk.Objects.StyleContext as Gtk.StyleContext
newtype IconInfo = IconInfo (SP.ManagedPtr IconInfo)
    deriving (IconInfo -> IconInfo -> Bool
(IconInfo -> IconInfo -> Bool)
-> (IconInfo -> IconInfo -> Bool) -> Eq IconInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IconInfo -> IconInfo -> Bool
$c/= :: IconInfo -> IconInfo -> Bool
== :: IconInfo -> IconInfo -> Bool
$c== :: IconInfo -> IconInfo -> Bool
Eq)
instance SP.ManagedPtrNewtype IconInfo where
    toManagedPtr :: IconInfo -> ManagedPtr IconInfo
toManagedPtr (IconInfo ManagedPtr IconInfo
p) = ManagedPtr IconInfo
p
foreign import ccall "gtk_icon_info_get_type"
    c_gtk_icon_info_get_type :: IO B.Types.GType
instance B.Types.TypedObject IconInfo where
    glibType :: IO GType
glibType = IO GType
c_gtk_icon_info_get_type
instance B.Types.GObject IconInfo
class (SP.GObject o, O.IsDescendantOf IconInfo o) => IsIconInfo o
instance (SP.GObject o, O.IsDescendantOf IconInfo o) => IsIconInfo o
instance O.HasParentTypes IconInfo
type instance O.ParentTypes IconInfo = '[GObject.Object.Object]
toIconInfo :: (MIO.MonadIO m, IsIconInfo o) => o -> m IconInfo
toIconInfo :: forall (m :: * -> *) o.
(MonadIO m, IsIconInfo o) =>
o -> m IconInfo
toIconInfo = IO IconInfo -> m IconInfo
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO IconInfo -> m IconInfo)
-> (o -> IO IconInfo) -> o -> m IconInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr IconInfo -> IconInfo) -> o -> IO IconInfo
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr IconInfo -> IconInfo
IconInfo
instance B.GValue.IsGValue (Maybe IconInfo) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_icon_info_get_type
    gvalueSet_ :: Ptr GValue -> Maybe IconInfo -> IO ()
gvalueSet_ Ptr GValue
gv Maybe IconInfo
P.Nothing = Ptr GValue -> Ptr IconInfo -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr IconInfo
forall a. Ptr a
FP.nullPtr :: FP.Ptr IconInfo)
    gvalueSet_ Ptr GValue
gv (P.Just IconInfo
obj) = IconInfo -> (Ptr IconInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr IconInfo
obj (Ptr GValue -> Ptr IconInfo -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe IconInfo)
gvalueGet_ Ptr GValue
gv = do
        Ptr IconInfo
ptr <- Ptr GValue -> IO (Ptr IconInfo)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr IconInfo)
        if Ptr IconInfo
ptr Ptr IconInfo -> Ptr IconInfo -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr IconInfo
forall a. Ptr a
FP.nullPtr
        then IconInfo -> Maybe IconInfo
forall a. a -> Maybe a
P.Just (IconInfo -> Maybe IconInfo) -> IO IconInfo -> IO (Maybe IconInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr IconInfo -> IconInfo) -> Ptr IconInfo -> IO IconInfo
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr IconInfo -> IconInfo
IconInfo Ptr IconInfo
ptr
        else Maybe IconInfo -> IO (Maybe IconInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe IconInfo
forall a. Maybe a
P.Nothing
        
    
#if defined(ENABLE_OVERLOADING)
type family ResolveIconInfoMethod (t :: Symbol) (o :: *) :: * where
    ResolveIconInfoMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveIconInfoMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveIconInfoMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveIconInfoMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveIconInfoMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveIconInfoMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveIconInfoMethod "isSymbolic" o = IconInfoIsSymbolicMethodInfo
    ResolveIconInfoMethod "loadIcon" o = IconInfoLoadIconMethodInfo
    ResolveIconInfoMethod "loadIconAsync" o = IconInfoLoadIconAsyncMethodInfo
    ResolveIconInfoMethod "loadIconFinish" o = IconInfoLoadIconFinishMethodInfo
    ResolveIconInfoMethod "loadSurface" o = IconInfoLoadSurfaceMethodInfo
    ResolveIconInfoMethod "loadSymbolic" o = IconInfoLoadSymbolicMethodInfo
    ResolveIconInfoMethod "loadSymbolicAsync" o = IconInfoLoadSymbolicAsyncMethodInfo
    ResolveIconInfoMethod "loadSymbolicFinish" o = IconInfoLoadSymbolicFinishMethodInfo
    ResolveIconInfoMethod "loadSymbolicForContext" o = IconInfoLoadSymbolicForContextMethodInfo
    ResolveIconInfoMethod "loadSymbolicForContextAsync" o = IconInfoLoadSymbolicForContextAsyncMethodInfo
    ResolveIconInfoMethod "loadSymbolicForContextFinish" o = IconInfoLoadSymbolicForContextFinishMethodInfo
    ResolveIconInfoMethod "loadSymbolicForStyle" o = IconInfoLoadSymbolicForStyleMethodInfo
    ResolveIconInfoMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveIconInfoMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveIconInfoMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveIconInfoMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveIconInfoMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveIconInfoMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveIconInfoMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveIconInfoMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveIconInfoMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveIconInfoMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveIconInfoMethod "getAttachPoints" o = IconInfoGetAttachPointsMethodInfo
    ResolveIconInfoMethod "getBaseScale" o = IconInfoGetBaseScaleMethodInfo
    ResolveIconInfoMethod "getBaseSize" o = IconInfoGetBaseSizeMethodInfo
    ResolveIconInfoMethod "getBuiltinPixbuf" o = IconInfoGetBuiltinPixbufMethodInfo
    ResolveIconInfoMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveIconInfoMethod "getDisplayName" o = IconInfoGetDisplayNameMethodInfo
    ResolveIconInfoMethod "getEmbeddedRect" o = IconInfoGetEmbeddedRectMethodInfo
    ResolveIconInfoMethod "getFilename" o = IconInfoGetFilenameMethodInfo
    ResolveIconInfoMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveIconInfoMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveIconInfoMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveIconInfoMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveIconInfoMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveIconInfoMethod "setRawCoordinates" o = IconInfoSetRawCoordinatesMethodInfo
    ResolveIconInfoMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveIconInfoMethod t IconInfo, O.OverloadedMethod info IconInfo p) => OL.IsLabel t (IconInfo -> 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 ~ ResolveIconInfoMethod t IconInfo, O.OverloadedMethod info IconInfo p, R.HasField t IconInfo p) => R.HasField t IconInfo p where
    getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveIconInfoMethod t IconInfo, O.OverloadedMethodInfo info IconInfo) => OL.IsLabel t (O.MethodProxy info IconInfo) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList IconInfo
type instance O.AttributeList IconInfo = IconInfoAttributeList
type IconInfoAttributeList = ('[ ] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList IconInfo = IconInfoSignalList
type IconInfoSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "gtk_icon_info_new_for_pixbuf" gtk_icon_info_new_for_pixbuf :: 
    Ptr Gtk.IconTheme.IconTheme ->          
    Ptr GdkPixbuf.Pixbuf.Pixbuf ->          
    IO (Ptr IconInfo)
iconInfoNewForPixbuf ::
    (B.CallStack.HasCallStack, MonadIO m, Gtk.IconTheme.IsIconTheme a, GdkPixbuf.Pixbuf.IsPixbuf b) =>
    a
    
    -> b
    
    -> m IconInfo
    
iconInfoNewForPixbuf :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsIconTheme a, IsPixbuf b) =>
a -> b -> m IconInfo
iconInfoNewForPixbuf a
iconTheme b
pixbuf = IO IconInfo -> m IconInfo
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO IconInfo -> m IconInfo) -> IO IconInfo -> m IconInfo
forall a b. (a -> b) -> a -> b
$ do
    Ptr IconTheme
iconTheme' <- a -> IO (Ptr IconTheme)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iconTheme
    Ptr Pixbuf
pixbuf' <- b -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
pixbuf
    Ptr IconInfo
result <- Ptr IconTheme -> Ptr Pixbuf -> IO (Ptr IconInfo)
gtk_icon_info_new_for_pixbuf Ptr IconTheme
iconTheme' Ptr Pixbuf
pixbuf'
    Text -> Ptr IconInfo -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iconInfoNewForPixbuf" Ptr IconInfo
result
    IconInfo
result' <- ((ManagedPtr IconInfo -> IconInfo) -> Ptr IconInfo -> IO IconInfo
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr IconInfo -> IconInfo
IconInfo) Ptr IconInfo
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconTheme
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
pixbuf
    IconInfo -> IO IconInfo
forall (m :: * -> *) a. Monad m => a -> m a
return IconInfo
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_icon_info_get_attach_points" gtk_icon_info_get_attach_points :: 
    Ptr IconInfo ->                         
    Ptr (Ptr Gdk.Point.Point) ->            
    Ptr Int32 ->                            
    IO CInt
{-# DEPRECATED iconInfoGetAttachPoints ["(Since version 3.14)","Attachment points are deprecated"] #-}
iconInfoGetAttachPoints ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconInfo a) =>
    a
    
    -> m ((Bool, [Gdk.Point.Point]))
    
iconInfoGetAttachPoints :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIconInfo a) =>
a -> m (Bool, [Point])
iconInfoGetAttachPoints a
iconInfo = IO (Bool, [Point]) -> m (Bool, [Point])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, [Point]) -> m (Bool, [Point]))
-> IO (Bool, [Point]) -> m (Bool, [Point])
forall a b. (a -> b) -> a -> b
$ do
    Ptr IconInfo
iconInfo' <- a -> IO (Ptr IconInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iconInfo
    Ptr (Ptr Point)
points <- IO (Ptr (Ptr Point))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (Ptr Gdk.Point.Point))
    Ptr Int32
nPoints <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    CInt
result <- Ptr IconInfo -> Ptr (Ptr Point) -> Ptr Int32 -> IO CInt
gtk_icon_info_get_attach_points Ptr IconInfo
iconInfo' Ptr (Ptr Point)
points Ptr Int32
nPoints
    Int32
nPoints' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
nPoints
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Ptr Point
points' <- Ptr (Ptr Point) -> IO (Ptr Point)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr Point)
points
    [Ptr Point]
points'' <- (Int -> Int32 -> Ptr Point -> IO [Ptr Point]
forall a b. Integral a => Int -> a -> Ptr b -> IO [Ptr b]
unpackBlockArrayWithLength Int
8 Int32
nPoints') Ptr Point
points'
    [Point]
points''' <- (Ptr Point -> IO Point) -> [Ptr Point] -> IO [Point]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr Point -> Point) -> Ptr Point -> IO Point
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr Point -> Point
Gdk.Point.Point) [Ptr Point]
points''
    Ptr Point -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Point
points'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconInfo
    Ptr (Ptr Point) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr Point)
points
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
nPoints
    (Bool, [Point]) -> IO (Bool, [Point])
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', [Point]
points''')
#if defined(ENABLE_OVERLOADING)
data IconInfoGetAttachPointsMethodInfo
instance (signature ~ (m ((Bool, [Gdk.Point.Point]))), MonadIO m, IsIconInfo a) => O.OverloadedMethod IconInfoGetAttachPointsMethodInfo a signature where
    overloadedMethod = iconInfoGetAttachPoints
instance O.OverloadedMethodInfo IconInfoGetAttachPointsMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.IconInfo.iconInfoGetAttachPoints",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-IconInfo.html#v:iconInfoGetAttachPoints"
        }
#endif
foreign import ccall "gtk_icon_info_get_base_scale" gtk_icon_info_get_base_scale :: 
    Ptr IconInfo ->                         
    IO Int32
iconInfoGetBaseScale ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconInfo a) =>
    a
    
    -> m Int32
    
iconInfoGetBaseScale :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIconInfo a) =>
a -> m Int32
iconInfoGetBaseScale a
iconInfo = 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 IconInfo
iconInfo' <- a -> IO (Ptr IconInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iconInfo
    Int32
result <- Ptr IconInfo -> IO Int32
gtk_icon_info_get_base_scale Ptr IconInfo
iconInfo'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconInfo
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data IconInfoGetBaseScaleMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsIconInfo a) => O.OverloadedMethod IconInfoGetBaseScaleMethodInfo a signature where
    overloadedMethod = iconInfoGetBaseScale
instance O.OverloadedMethodInfo IconInfoGetBaseScaleMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.IconInfo.iconInfoGetBaseScale",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-IconInfo.html#v:iconInfoGetBaseScale"
        }
#endif
foreign import ccall "gtk_icon_info_get_base_size" gtk_icon_info_get_base_size :: 
    Ptr IconInfo ->                         
    IO Int32
iconInfoGetBaseSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconInfo a) =>
    a
    
    -> m Int32
    
    
iconInfoGetBaseSize :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIconInfo a) =>
a -> m Int32
iconInfoGetBaseSize a
iconInfo = 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 IconInfo
iconInfo' <- a -> IO (Ptr IconInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iconInfo
    Int32
result <- Ptr IconInfo -> IO Int32
gtk_icon_info_get_base_size Ptr IconInfo
iconInfo'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconInfo
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data IconInfoGetBaseSizeMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsIconInfo a) => O.OverloadedMethod IconInfoGetBaseSizeMethodInfo a signature where
    overloadedMethod = iconInfoGetBaseSize
instance O.OverloadedMethodInfo IconInfoGetBaseSizeMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.IconInfo.iconInfoGetBaseSize",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-IconInfo.html#v:iconInfoGetBaseSize"
        }
#endif
foreign import ccall "gtk_icon_info_get_builtin_pixbuf" gtk_icon_info_get_builtin_pixbuf :: 
    Ptr IconInfo ->                         
    IO (Ptr GdkPixbuf.Pixbuf.Pixbuf)
{-# DEPRECATED iconInfoGetBuiltinPixbuf ["(Since version 3.14)","This function is deprecated, use","    'GI.Gtk.Objects.IconTheme.iconThemeAddResourcePath' instead of builtin icons."] #-}
iconInfoGetBuiltinPixbuf ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconInfo a) =>
    a
    
    -> m (Maybe GdkPixbuf.Pixbuf.Pixbuf)
    
    
    
    
iconInfoGetBuiltinPixbuf :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIconInfo a) =>
a -> m (Maybe Pixbuf)
iconInfoGetBuiltinPixbuf a
iconInfo = IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Pixbuf) -> m (Maybe Pixbuf))
-> IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ do
    Ptr IconInfo
iconInfo' <- a -> IO (Ptr IconInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iconInfo
    Ptr Pixbuf
result <- Ptr IconInfo -> IO (Ptr Pixbuf)
gtk_icon_info_get_builtin_pixbuf Ptr IconInfo
iconInfo'
    Maybe Pixbuf
maybeResult <- Ptr Pixbuf -> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Pixbuf
result ((Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf))
-> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ \Ptr Pixbuf
result' -> do
        Pixbuf
result'' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Pixbuf -> Pixbuf
GdkPixbuf.Pixbuf.Pixbuf) Ptr Pixbuf
result'
        Pixbuf -> IO Pixbuf
forall (m :: * -> *) a. Monad m => a -> m a
return Pixbuf
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconInfo
    Maybe Pixbuf -> IO (Maybe Pixbuf)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Pixbuf
maybeResult
#if defined(ENABLE_OVERLOADING)
data IconInfoGetBuiltinPixbufMethodInfo
instance (signature ~ (m (Maybe GdkPixbuf.Pixbuf.Pixbuf)), MonadIO m, IsIconInfo a) => O.OverloadedMethod IconInfoGetBuiltinPixbufMethodInfo a signature where
    overloadedMethod = iconInfoGetBuiltinPixbuf
instance O.OverloadedMethodInfo IconInfoGetBuiltinPixbufMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.IconInfo.iconInfoGetBuiltinPixbuf",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-IconInfo.html#v:iconInfoGetBuiltinPixbuf"
        }
#endif
foreign import ccall "gtk_icon_info_get_display_name" gtk_icon_info_get_display_name :: 
    Ptr IconInfo ->                         
    IO CString
{-# DEPRECATED iconInfoGetDisplayName ["(Since version 3.14)","Display names are deprecated"] #-}
iconInfoGetDisplayName ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconInfo a) =>
    a
    
    -> m T.Text
    
iconInfoGetDisplayName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIconInfo a) =>
a -> m Text
iconInfoGetDisplayName a
iconInfo = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr IconInfo
iconInfo' <- a -> IO (Ptr IconInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iconInfo
    CString
result <- Ptr IconInfo -> IO CString
gtk_icon_info_get_display_name Ptr IconInfo
iconInfo'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iconInfoGetDisplayName" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconInfo
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data IconInfoGetDisplayNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsIconInfo a) => O.OverloadedMethod IconInfoGetDisplayNameMethodInfo a signature where
    overloadedMethod = iconInfoGetDisplayName
instance O.OverloadedMethodInfo IconInfoGetDisplayNameMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.IconInfo.iconInfoGetDisplayName",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-IconInfo.html#v:iconInfoGetDisplayName"
        }
#endif
foreign import ccall "gtk_icon_info_get_embedded_rect" gtk_icon_info_get_embedded_rect :: 
    Ptr IconInfo ->                         
    Ptr Gdk.Rectangle.Rectangle ->          
    IO CInt
{-# DEPRECATED iconInfoGetEmbeddedRect ["(Since version 3.14)","Embedded rectangles are deprecated"] #-}
iconInfoGetEmbeddedRect ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconInfo a) =>
    a
    
    -> m ((Bool, Gdk.Rectangle.Rectangle))
    
iconInfoGetEmbeddedRect :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIconInfo a) =>
a -> m (Bool, Rectangle)
iconInfoGetEmbeddedRect a
iconInfo = IO (Bool, Rectangle) -> m (Bool, Rectangle)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Rectangle) -> m (Bool, Rectangle))
-> IO (Bool, Rectangle) -> m (Bool, Rectangle)
forall a b. (a -> b) -> a -> b
$ do
    Ptr IconInfo
iconInfo' <- a -> IO (Ptr IconInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iconInfo
    Ptr Rectangle
rectangle <- Int -> IO (Ptr Rectangle)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Gdk.Rectangle.Rectangle)
    CInt
result <- Ptr IconInfo -> Ptr Rectangle -> IO CInt
gtk_icon_info_get_embedded_rect Ptr IconInfo
iconInfo' Ptr Rectangle
rectangle
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Rectangle
rectangle' <- ((ManagedPtr Rectangle -> Rectangle)
-> Ptr Rectangle -> IO Rectangle
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Rectangle -> Rectangle
Gdk.Rectangle.Rectangle) Ptr Rectangle
rectangle
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconInfo
    (Bool, Rectangle) -> IO (Bool, Rectangle)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Rectangle
rectangle')
#if defined(ENABLE_OVERLOADING)
data IconInfoGetEmbeddedRectMethodInfo
instance (signature ~ (m ((Bool, Gdk.Rectangle.Rectangle))), MonadIO m, IsIconInfo a) => O.OverloadedMethod IconInfoGetEmbeddedRectMethodInfo a signature where
    overloadedMethod = iconInfoGetEmbeddedRect
instance O.OverloadedMethodInfo IconInfoGetEmbeddedRectMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.IconInfo.iconInfoGetEmbeddedRect",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-IconInfo.html#v:iconInfoGetEmbeddedRect"
        }
#endif
foreign import ccall "gtk_icon_info_get_filename" gtk_icon_info_get_filename :: 
    Ptr IconInfo ->                         
    IO CString
iconInfoGetFilename ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconInfo a) =>
    a
    
    -> m (Maybe [Char])
    
    
    
    
iconInfoGetFilename :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIconInfo a) =>
a -> m (Maybe [Char])
iconInfoGetFilename a
iconInfo = IO (Maybe [Char]) -> m (Maybe [Char])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe [Char]) -> m (Maybe [Char]))
-> IO (Maybe [Char]) -> m (Maybe [Char])
forall a b. (a -> b) -> a -> b
$ do
    Ptr IconInfo
iconInfo' <- a -> IO (Ptr IconInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iconInfo
    CString
result <- Ptr IconInfo -> IO CString
gtk_icon_info_get_filename Ptr IconInfo
iconInfo'
    Maybe [Char]
maybeResult <- CString -> (CString -> IO [Char]) -> IO (Maybe [Char])
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO [Char]) -> IO (Maybe [Char]))
-> (CString -> IO [Char]) -> IO (Maybe [Char])
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        [Char]
result'' <- HasCallStack => CString -> IO [Char]
CString -> IO [Char]
cstringToString CString
result'
        [Char] -> IO [Char]
forall (m :: * -> *) a. Monad m => a -> m a
return [Char]
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconInfo
    Maybe [Char] -> IO (Maybe [Char])
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe [Char]
maybeResult
#if defined(ENABLE_OVERLOADING)
data IconInfoGetFilenameMethodInfo
instance (signature ~ (m (Maybe [Char])), MonadIO m, IsIconInfo a) => O.OverloadedMethod IconInfoGetFilenameMethodInfo a signature where
    overloadedMethod = iconInfoGetFilename
instance O.OverloadedMethodInfo IconInfoGetFilenameMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.IconInfo.iconInfoGetFilename",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-IconInfo.html#v:iconInfoGetFilename"
        }
#endif
foreign import ccall "gtk_icon_info_is_symbolic" gtk_icon_info_is_symbolic :: 
    Ptr IconInfo ->                         
    IO CInt
iconInfoIsSymbolic ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconInfo a) =>
    a
    
    -> m Bool
    
iconInfoIsSymbolic :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIconInfo a) =>
a -> m Bool
iconInfoIsSymbolic a
iconInfo = 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 IconInfo
iconInfo' <- a -> IO (Ptr IconInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iconInfo
    CInt
result <- Ptr IconInfo -> IO CInt
gtk_icon_info_is_symbolic Ptr IconInfo
iconInfo'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconInfo
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data IconInfoIsSymbolicMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsIconInfo a) => O.OverloadedMethod IconInfoIsSymbolicMethodInfo a signature where
    overloadedMethod = iconInfoIsSymbolic
instance O.OverloadedMethodInfo IconInfoIsSymbolicMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.IconInfo.iconInfoIsSymbolic",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-IconInfo.html#v:iconInfoIsSymbolic"
        }
#endif
foreign import ccall "gtk_icon_info_load_icon" gtk_icon_info_load_icon :: 
    Ptr IconInfo ->                         
    Ptr (Ptr GError) ->                     
    IO (Ptr GdkPixbuf.Pixbuf.Pixbuf)
iconInfoLoadIcon ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconInfo a) =>
    a
    
    -> m GdkPixbuf.Pixbuf.Pixbuf
    
    
    
    
iconInfoLoadIcon :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIconInfo a) =>
a -> m Pixbuf
iconInfoLoadIcon a
iconInfo = IO Pixbuf -> m Pixbuf
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Pixbuf -> m Pixbuf) -> IO Pixbuf -> m Pixbuf
forall a b. (a -> b) -> a -> b
$ do
    Ptr IconInfo
iconInfo' <- a -> IO (Ptr IconInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iconInfo
    IO Pixbuf -> IO () -> IO Pixbuf
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr Pixbuf
result <- (Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf))
-> (Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a b. (a -> b) -> a -> b
$ Ptr IconInfo -> Ptr (Ptr GError) -> IO (Ptr Pixbuf)
gtk_icon_info_load_icon Ptr IconInfo
iconInfo'
        Text -> Ptr Pixbuf -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iconInfoLoadIcon" Ptr Pixbuf
result
        Pixbuf
result' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Pixbuf -> Pixbuf
GdkPixbuf.Pixbuf.Pixbuf) Ptr Pixbuf
result
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconInfo
        Pixbuf -> IO Pixbuf
forall (m :: * -> *) a. Monad m => a -> m a
return Pixbuf
result'
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )
#if defined(ENABLE_OVERLOADING)
data IconInfoLoadIconMethodInfo
instance (signature ~ (m GdkPixbuf.Pixbuf.Pixbuf), MonadIO m, IsIconInfo a) => O.OverloadedMethod IconInfoLoadIconMethodInfo a signature where
    overloadedMethod = iconInfoLoadIcon
instance O.OverloadedMethodInfo IconInfoLoadIconMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.IconInfo.iconInfoLoadIcon",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-IconInfo.html#v:iconInfoLoadIcon"
        }
#endif
foreign import ccall "gtk_icon_info_load_icon_async" gtk_icon_info_load_icon_async :: 
    Ptr IconInfo ->                         
    Ptr Gio.Cancellable.Cancellable ->      
    FunPtr Gio.Callbacks.C_AsyncReadyCallback -> 
    Ptr () ->                               
    IO ()
iconInfoLoadIconAsync ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconInfo a, Gio.Cancellable.IsCancellable b) =>
    a
    
    -> Maybe (b)
    
    -> Maybe (Gio.Callbacks.AsyncReadyCallback)
    
    
    -> m ()
iconInfoLoadIconAsync :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsIconInfo a, IsCancellable b) =>
a -> Maybe b -> Maybe AsyncReadyCallback -> m ()
iconInfoLoadIconAsync a
iconInfo Maybe b
cancellable Maybe AsyncReadyCallback
callback = 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 IconInfo
iconInfo' <- a -> IO (Ptr IconInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iconInfo
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just b
jCancellable -> do
            Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
        Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just AsyncReadyCallback
jCallback -> do
            Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
            FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
            Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
            FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr IconInfo
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
gtk_icon_info_load_icon_async Ptr IconInfo
iconInfo' Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconInfo
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data IconInfoLoadIconAsyncMethodInfo
instance (signature ~ (Maybe (b) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsIconInfo a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod IconInfoLoadIconAsyncMethodInfo a signature where
    overloadedMethod = iconInfoLoadIconAsync
instance O.OverloadedMethodInfo IconInfoLoadIconAsyncMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.IconInfo.iconInfoLoadIconAsync",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-IconInfo.html#v:iconInfoLoadIconAsync"
        }
#endif
foreign import ccall "gtk_icon_info_load_icon_finish" gtk_icon_info_load_icon_finish :: 
    Ptr IconInfo ->                         
    Ptr Gio.AsyncResult.AsyncResult ->      
    Ptr (Ptr GError) ->                     
    IO (Ptr GdkPixbuf.Pixbuf.Pixbuf)
iconInfoLoadIconFinish ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconInfo a, Gio.AsyncResult.IsAsyncResult b) =>
    a
    
    -> b
    
    -> m GdkPixbuf.Pixbuf.Pixbuf
    
    
    
    
iconInfoLoadIconFinish :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsIconInfo a, IsAsyncResult b) =>
a -> b -> m Pixbuf
iconInfoLoadIconFinish a
iconInfo b
res = IO Pixbuf -> m Pixbuf
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Pixbuf -> m Pixbuf) -> IO Pixbuf -> m Pixbuf
forall a b. (a -> b) -> a -> b
$ do
    Ptr IconInfo
iconInfo' <- a -> IO (Ptr IconInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iconInfo
    Ptr AsyncResult
res' <- b -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
res
    IO Pixbuf -> IO () -> IO Pixbuf
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr Pixbuf
result <- (Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf))
-> (Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a b. (a -> b) -> a -> b
$ Ptr IconInfo
-> Ptr AsyncResult -> Ptr (Ptr GError) -> IO (Ptr Pixbuf)
gtk_icon_info_load_icon_finish Ptr IconInfo
iconInfo' Ptr AsyncResult
res'
        Text -> Ptr Pixbuf -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iconInfoLoadIconFinish" Ptr Pixbuf
result
        Pixbuf
result' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Pixbuf -> Pixbuf
GdkPixbuf.Pixbuf.Pixbuf) Ptr Pixbuf
result
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconInfo
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
res
        Pixbuf -> IO Pixbuf
forall (m :: * -> *) a. Monad m => a -> m a
return Pixbuf
result'
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )
#if defined(ENABLE_OVERLOADING)
data IconInfoLoadIconFinishMethodInfo
instance (signature ~ (b -> m GdkPixbuf.Pixbuf.Pixbuf), MonadIO m, IsIconInfo a, Gio.AsyncResult.IsAsyncResult b) => O.OverloadedMethod IconInfoLoadIconFinishMethodInfo a signature where
    overloadedMethod = iconInfoLoadIconFinish
instance O.OverloadedMethodInfo IconInfoLoadIconFinishMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.IconInfo.iconInfoLoadIconFinish",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-IconInfo.html#v:iconInfoLoadIconFinish"
        }
#endif
foreign import ccall "gtk_icon_info_load_surface" gtk_icon_info_load_surface :: 
    Ptr IconInfo ->                         
    Ptr Gdk.Window.Window ->                
    Ptr (Ptr GError) ->                     
    IO (Ptr Cairo.Surface.Surface)
iconInfoLoadSurface ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconInfo a, Gdk.Window.IsWindow b) =>
    a
    
    -> Maybe (b)
    
    -> m Cairo.Surface.Surface
    
    
    
    
iconInfoLoadSurface :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsIconInfo a, IsWindow b) =>
a -> Maybe b -> m Surface
iconInfoLoadSurface a
iconInfo Maybe b
forWindow = IO Surface -> m Surface
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Surface -> m Surface) -> IO Surface -> m Surface
forall a b. (a -> b) -> a -> b
$ do
    Ptr IconInfo
iconInfo' <- a -> IO (Ptr IconInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iconInfo
    Ptr Window
maybeForWindow <- case Maybe b
forWindow of
        Maybe b
Nothing -> Ptr Window -> IO (Ptr Window)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Window
forall a. Ptr a
nullPtr
        Just b
jForWindow -> do
            Ptr Window
jForWindow' <- b -> IO (Ptr Window)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jForWindow
            Ptr Window -> IO (Ptr Window)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Window
jForWindow'
    IO Surface -> IO () -> IO Surface
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr Surface
result <- (Ptr (Ptr GError) -> IO (Ptr Surface)) -> IO (Ptr Surface)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Surface)) -> IO (Ptr Surface))
-> (Ptr (Ptr GError) -> IO (Ptr Surface)) -> IO (Ptr Surface)
forall a b. (a -> b) -> a -> b
$ Ptr IconInfo -> Ptr Window -> Ptr (Ptr GError) -> IO (Ptr Surface)
gtk_icon_info_load_surface Ptr IconInfo
iconInfo' Ptr Window
maybeForWindow
        Text -> Ptr Surface -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iconInfoLoadSurface" Ptr Surface
result
        Surface
result' <- ((ManagedPtr Surface -> Surface) -> Ptr Surface -> IO Surface
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Surface -> Surface
Cairo.Surface.Surface) Ptr Surface
result
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconInfo
        Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
forWindow b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        Surface -> IO Surface
forall (m :: * -> *) a. Monad m => a -> m a
return Surface
result'
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )
#if defined(ENABLE_OVERLOADING)
data IconInfoLoadSurfaceMethodInfo
instance (signature ~ (Maybe (b) -> m Cairo.Surface.Surface), MonadIO m, IsIconInfo a, Gdk.Window.IsWindow b) => O.OverloadedMethod IconInfoLoadSurfaceMethodInfo a signature where
    overloadedMethod = iconInfoLoadSurface
instance O.OverloadedMethodInfo IconInfoLoadSurfaceMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.IconInfo.iconInfoLoadSurface",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-IconInfo.html#v:iconInfoLoadSurface"
        }
#endif
foreign import ccall "gtk_icon_info_load_symbolic" gtk_icon_info_load_symbolic :: 
    Ptr IconInfo ->                         
    Ptr Gdk.RGBA.RGBA ->                    
    Ptr Gdk.RGBA.RGBA ->                    
    Ptr Gdk.RGBA.RGBA ->                    
    Ptr Gdk.RGBA.RGBA ->                    
    Ptr CInt ->                             
    Ptr (Ptr GError) ->                     
    IO (Ptr GdkPixbuf.Pixbuf.Pixbuf)
iconInfoLoadSymbolic ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconInfo a) =>
    a
    
    -> Gdk.RGBA.RGBA
    
    -> Maybe (Gdk.RGBA.RGBA)
    
    
    -> Maybe (Gdk.RGBA.RGBA)
    
    
    -> Maybe (Gdk.RGBA.RGBA)
    
    
    -> m ((GdkPixbuf.Pixbuf.Pixbuf, Bool))
    
iconInfoLoadSymbolic :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIconInfo a) =>
a
-> RGBA
-> Maybe RGBA
-> Maybe RGBA
-> Maybe RGBA
-> m (Pixbuf, Bool)
iconInfoLoadSymbolic a
iconInfo RGBA
fg Maybe RGBA
successColor Maybe RGBA
warningColor Maybe RGBA
errorColor = IO (Pixbuf, Bool) -> m (Pixbuf, Bool)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Pixbuf, Bool) -> m (Pixbuf, Bool))
-> IO (Pixbuf, Bool) -> m (Pixbuf, Bool)
forall a b. (a -> b) -> a -> b
$ do
    Ptr IconInfo
iconInfo' <- a -> IO (Ptr IconInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iconInfo
    Ptr RGBA
fg' <- RGBA -> IO (Ptr RGBA)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RGBA
fg
    Ptr RGBA
maybeSuccessColor <- case Maybe RGBA
successColor of
        Maybe RGBA
Nothing -> Ptr RGBA -> IO (Ptr RGBA)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr RGBA
forall a. Ptr a
nullPtr
        Just RGBA
jSuccessColor -> do
            Ptr RGBA
jSuccessColor' <- RGBA -> IO (Ptr RGBA)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RGBA
jSuccessColor
            Ptr RGBA -> IO (Ptr RGBA)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr RGBA
jSuccessColor'
    Ptr RGBA
maybeWarningColor <- case Maybe RGBA
warningColor of
        Maybe RGBA
Nothing -> Ptr RGBA -> IO (Ptr RGBA)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr RGBA
forall a. Ptr a
nullPtr
        Just RGBA
jWarningColor -> do
            Ptr RGBA
jWarningColor' <- RGBA -> IO (Ptr RGBA)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RGBA
jWarningColor
            Ptr RGBA -> IO (Ptr RGBA)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr RGBA
jWarningColor'
    Ptr RGBA
maybeErrorColor <- case Maybe RGBA
errorColor of
        Maybe RGBA
Nothing -> Ptr RGBA -> IO (Ptr RGBA)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr RGBA
forall a. Ptr a
nullPtr
        Just RGBA
jErrorColor -> do
            Ptr RGBA
jErrorColor' <- RGBA -> IO (Ptr RGBA)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RGBA
jErrorColor
            Ptr RGBA -> IO (Ptr RGBA)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr RGBA
jErrorColor'
    Ptr CInt
wasSymbolic <- IO (Ptr CInt)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CInt)
    IO (Pixbuf, Bool) -> IO () -> IO (Pixbuf, Bool)
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr Pixbuf
result <- (Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf))
-> (Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a b. (a -> b) -> a -> b
$ Ptr IconInfo
-> Ptr RGBA
-> Ptr RGBA
-> Ptr RGBA
-> Ptr RGBA
-> Ptr CInt
-> Ptr (Ptr GError)
-> IO (Ptr Pixbuf)
gtk_icon_info_load_symbolic Ptr IconInfo
iconInfo' Ptr RGBA
fg' Ptr RGBA
maybeSuccessColor Ptr RGBA
maybeWarningColor Ptr RGBA
maybeErrorColor Ptr CInt
wasSymbolic
        Text -> Ptr Pixbuf -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iconInfoLoadSymbolic" Ptr Pixbuf
result
        Pixbuf
result' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Pixbuf -> Pixbuf
GdkPixbuf.Pixbuf.Pixbuf) Ptr Pixbuf
result
        CInt
wasSymbolic' <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
wasSymbolic
        let wasSymbolic'' :: Bool
wasSymbolic'' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
wasSymbolic'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconInfo
        RGBA -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RGBA
fg
        Maybe RGBA -> (RGBA -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe RGBA
successColor RGBA -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        Maybe RGBA -> (RGBA -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe RGBA
warningColor RGBA -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        Maybe RGBA -> (RGBA -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe RGBA
errorColor RGBA -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        Ptr CInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CInt
wasSymbolic
        (Pixbuf, Bool) -> IO (Pixbuf, Bool)
forall (m :: * -> *) a. Monad m => a -> m a
return (Pixbuf
result', Bool
wasSymbolic'')
     ) (do
        Ptr CInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CInt
wasSymbolic
     )
#if defined(ENABLE_OVERLOADING)
data IconInfoLoadSymbolicMethodInfo
instance (signature ~ (Gdk.RGBA.RGBA -> Maybe (Gdk.RGBA.RGBA) -> Maybe (Gdk.RGBA.RGBA) -> Maybe (Gdk.RGBA.RGBA) -> m ((GdkPixbuf.Pixbuf.Pixbuf, Bool))), MonadIO m, IsIconInfo a) => O.OverloadedMethod IconInfoLoadSymbolicMethodInfo a signature where
    overloadedMethod = iconInfoLoadSymbolic
instance O.OverloadedMethodInfo IconInfoLoadSymbolicMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.IconInfo.iconInfoLoadSymbolic",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-IconInfo.html#v:iconInfoLoadSymbolic"
        }
#endif
foreign import ccall "gtk_icon_info_load_symbolic_async" gtk_icon_info_load_symbolic_async :: 
    Ptr IconInfo ->                         
    Ptr Gdk.RGBA.RGBA ->                    
    Ptr Gdk.RGBA.RGBA ->                    
    Ptr Gdk.RGBA.RGBA ->                    
    Ptr Gdk.RGBA.RGBA ->                    
    Ptr Gio.Cancellable.Cancellable ->      
    FunPtr Gio.Callbacks.C_AsyncReadyCallback -> 
    Ptr () ->                               
    IO ()
iconInfoLoadSymbolicAsync ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconInfo a, Gio.Cancellable.IsCancellable b) =>
    a
    
    -> Gdk.RGBA.RGBA
    
    -> Maybe (Gdk.RGBA.RGBA)
    
    
    -> Maybe (Gdk.RGBA.RGBA)
    
    
    -> Maybe (Gdk.RGBA.RGBA)
    
    
    -> Maybe (b)
    
    
    -> Maybe (Gio.Callbacks.AsyncReadyCallback)
    
    
    -> m ()
iconInfoLoadSymbolicAsync :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsIconInfo a, IsCancellable b) =>
a
-> RGBA
-> Maybe RGBA
-> Maybe RGBA
-> Maybe RGBA
-> Maybe b
-> Maybe AsyncReadyCallback
-> m ()
iconInfoLoadSymbolicAsync a
iconInfo RGBA
fg Maybe RGBA
successColor Maybe RGBA
warningColor Maybe RGBA
errorColor Maybe b
cancellable Maybe AsyncReadyCallback
callback = 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 IconInfo
iconInfo' <- a -> IO (Ptr IconInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iconInfo
    Ptr RGBA
fg' <- RGBA -> IO (Ptr RGBA)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RGBA
fg
    Ptr RGBA
maybeSuccessColor <- case Maybe RGBA
successColor of
        Maybe RGBA
Nothing -> Ptr RGBA -> IO (Ptr RGBA)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr RGBA
forall a. Ptr a
nullPtr
        Just RGBA
jSuccessColor -> do
            Ptr RGBA
jSuccessColor' <- RGBA -> IO (Ptr RGBA)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RGBA
jSuccessColor
            Ptr RGBA -> IO (Ptr RGBA)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr RGBA
jSuccessColor'
    Ptr RGBA
maybeWarningColor <- case Maybe RGBA
warningColor of
        Maybe RGBA
Nothing -> Ptr RGBA -> IO (Ptr RGBA)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr RGBA
forall a. Ptr a
nullPtr
        Just RGBA
jWarningColor -> do
            Ptr RGBA
jWarningColor' <- RGBA -> IO (Ptr RGBA)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RGBA
jWarningColor
            Ptr RGBA -> IO (Ptr RGBA)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr RGBA
jWarningColor'
    Ptr RGBA
maybeErrorColor <- case Maybe RGBA
errorColor of
        Maybe RGBA
Nothing -> Ptr RGBA -> IO (Ptr RGBA)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr RGBA
forall a. Ptr a
nullPtr
        Just RGBA
jErrorColor -> do
            Ptr RGBA
jErrorColor' <- RGBA -> IO (Ptr RGBA)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RGBA
jErrorColor
            Ptr RGBA -> IO (Ptr RGBA)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr RGBA
jErrorColor'
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just b
jCancellable -> do
            Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
        Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just AsyncReadyCallback
jCallback -> do
            Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
            FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
            Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
            FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr IconInfo
-> Ptr RGBA
-> Ptr RGBA
-> Ptr RGBA
-> Ptr RGBA
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
gtk_icon_info_load_symbolic_async Ptr IconInfo
iconInfo' Ptr RGBA
fg' Ptr RGBA
maybeSuccessColor Ptr RGBA
maybeWarningColor Ptr RGBA
maybeErrorColor Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconInfo
    RGBA -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RGBA
fg
    Maybe RGBA -> (RGBA -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe RGBA
successColor RGBA -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Maybe RGBA -> (RGBA -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe RGBA
warningColor RGBA -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Maybe RGBA -> (RGBA -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe RGBA
errorColor RGBA -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data IconInfoLoadSymbolicAsyncMethodInfo
instance (signature ~ (Gdk.RGBA.RGBA -> Maybe (Gdk.RGBA.RGBA) -> Maybe (Gdk.RGBA.RGBA) -> Maybe (Gdk.RGBA.RGBA) -> Maybe (b) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsIconInfo a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod IconInfoLoadSymbolicAsyncMethodInfo a signature where
    overloadedMethod = iconInfoLoadSymbolicAsync
instance O.OverloadedMethodInfo IconInfoLoadSymbolicAsyncMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.IconInfo.iconInfoLoadSymbolicAsync",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-IconInfo.html#v:iconInfoLoadSymbolicAsync"
        }
#endif
foreign import ccall "gtk_icon_info_load_symbolic_finish" gtk_icon_info_load_symbolic_finish :: 
    Ptr IconInfo ->                         
    Ptr Gio.AsyncResult.AsyncResult ->      
    Ptr CInt ->                             
    Ptr (Ptr GError) ->                     
    IO (Ptr GdkPixbuf.Pixbuf.Pixbuf)
iconInfoLoadSymbolicFinish ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconInfo a, Gio.AsyncResult.IsAsyncResult b) =>
    a
    
    -> b
    
    -> m ((GdkPixbuf.Pixbuf.Pixbuf, Bool))
    
    
    
    
iconInfoLoadSymbolicFinish :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsIconInfo a, IsAsyncResult b) =>
a -> b -> m (Pixbuf, Bool)
iconInfoLoadSymbolicFinish a
iconInfo b
res = IO (Pixbuf, Bool) -> m (Pixbuf, Bool)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Pixbuf, Bool) -> m (Pixbuf, Bool))
-> IO (Pixbuf, Bool) -> m (Pixbuf, Bool)
forall a b. (a -> b) -> a -> b
$ do
    Ptr IconInfo
iconInfo' <- a -> IO (Ptr IconInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iconInfo
    Ptr AsyncResult
res' <- b -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
res
    Ptr CInt
wasSymbolic <- IO (Ptr CInt)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CInt)
    IO (Pixbuf, Bool) -> IO () -> IO (Pixbuf, Bool)
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr Pixbuf
result <- (Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf))
-> (Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a b. (a -> b) -> a -> b
$ Ptr IconInfo
-> Ptr AsyncResult
-> Ptr CInt
-> Ptr (Ptr GError)
-> IO (Ptr Pixbuf)
gtk_icon_info_load_symbolic_finish Ptr IconInfo
iconInfo' Ptr AsyncResult
res' Ptr CInt
wasSymbolic
        Text -> Ptr Pixbuf -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iconInfoLoadSymbolicFinish" Ptr Pixbuf
result
        Pixbuf
result' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Pixbuf -> Pixbuf
GdkPixbuf.Pixbuf.Pixbuf) Ptr Pixbuf
result
        CInt
wasSymbolic' <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
wasSymbolic
        let wasSymbolic'' :: Bool
wasSymbolic'' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
wasSymbolic'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconInfo
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
res
        Ptr CInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CInt
wasSymbolic
        (Pixbuf, Bool) -> IO (Pixbuf, Bool)
forall (m :: * -> *) a. Monad m => a -> m a
return (Pixbuf
result', Bool
wasSymbolic'')
     ) (do
        Ptr CInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CInt
wasSymbolic
     )
#if defined(ENABLE_OVERLOADING)
data IconInfoLoadSymbolicFinishMethodInfo
instance (signature ~ (b -> m ((GdkPixbuf.Pixbuf.Pixbuf, Bool))), MonadIO m, IsIconInfo a, Gio.AsyncResult.IsAsyncResult b) => O.OverloadedMethod IconInfoLoadSymbolicFinishMethodInfo a signature where
    overloadedMethod = iconInfoLoadSymbolicFinish
instance O.OverloadedMethodInfo IconInfoLoadSymbolicFinishMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.IconInfo.iconInfoLoadSymbolicFinish",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-IconInfo.html#v:iconInfoLoadSymbolicFinish"
        }
#endif
foreign import ccall "gtk_icon_info_load_symbolic_for_context" gtk_icon_info_load_symbolic_for_context :: 
    Ptr IconInfo ->                         
    Ptr Gtk.StyleContext.StyleContext ->    
    Ptr CInt ->                             
    Ptr (Ptr GError) ->                     
    IO (Ptr GdkPixbuf.Pixbuf.Pixbuf)
iconInfoLoadSymbolicForContext ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconInfo a, Gtk.StyleContext.IsStyleContext b) =>
    a
    
    -> b
    
    -> m ((GdkPixbuf.Pixbuf.Pixbuf, Bool))
    
iconInfoLoadSymbolicForContext :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsIconInfo a, IsStyleContext b) =>
a -> b -> m (Pixbuf, Bool)
iconInfoLoadSymbolicForContext a
iconInfo b
context = IO (Pixbuf, Bool) -> m (Pixbuf, Bool)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Pixbuf, Bool) -> m (Pixbuf, Bool))
-> IO (Pixbuf, Bool) -> m (Pixbuf, Bool)
forall a b. (a -> b) -> a -> b
$ do
    Ptr IconInfo
iconInfo' <- a -> IO (Ptr IconInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iconInfo
    Ptr StyleContext
context' <- b -> IO (Ptr StyleContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
context
    Ptr CInt
wasSymbolic <- IO (Ptr CInt)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CInt)
    IO (Pixbuf, Bool) -> IO () -> IO (Pixbuf, Bool)
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr Pixbuf
result <- (Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf))
-> (Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a b. (a -> b) -> a -> b
$ Ptr IconInfo
-> Ptr StyleContext
-> Ptr CInt
-> Ptr (Ptr GError)
-> IO (Ptr Pixbuf)
gtk_icon_info_load_symbolic_for_context Ptr IconInfo
iconInfo' Ptr StyleContext
context' Ptr CInt
wasSymbolic
        Text -> Ptr Pixbuf -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iconInfoLoadSymbolicForContext" Ptr Pixbuf
result
        Pixbuf
result' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Pixbuf -> Pixbuf
GdkPixbuf.Pixbuf.Pixbuf) Ptr Pixbuf
result
        CInt
wasSymbolic' <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
wasSymbolic
        let wasSymbolic'' :: Bool
wasSymbolic'' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
wasSymbolic'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconInfo
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
context
        Ptr CInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CInt
wasSymbolic
        (Pixbuf, Bool) -> IO (Pixbuf, Bool)
forall (m :: * -> *) a. Monad m => a -> m a
return (Pixbuf
result', Bool
wasSymbolic'')
     ) (do
        Ptr CInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CInt
wasSymbolic
     )
#if defined(ENABLE_OVERLOADING)
data IconInfoLoadSymbolicForContextMethodInfo
instance (signature ~ (b -> m ((GdkPixbuf.Pixbuf.Pixbuf, Bool))), MonadIO m, IsIconInfo a, Gtk.StyleContext.IsStyleContext b) => O.OverloadedMethod IconInfoLoadSymbolicForContextMethodInfo a signature where
    overloadedMethod = iconInfoLoadSymbolicForContext
instance O.OverloadedMethodInfo IconInfoLoadSymbolicForContextMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.IconInfo.iconInfoLoadSymbolicForContext",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-IconInfo.html#v:iconInfoLoadSymbolicForContext"
        }
#endif
foreign import ccall "gtk_icon_info_load_symbolic_for_context_async" gtk_icon_info_load_symbolic_for_context_async :: 
    Ptr IconInfo ->                         
    Ptr Gtk.StyleContext.StyleContext ->    
    Ptr Gio.Cancellable.Cancellable ->      
    FunPtr Gio.Callbacks.C_AsyncReadyCallback -> 
    Ptr () ->                               
    IO ()
iconInfoLoadSymbolicForContextAsync ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconInfo a, Gtk.StyleContext.IsStyleContext b, Gio.Cancellable.IsCancellable c) =>
    a
    
    -> b
    
    -> Maybe (c)
    
    
    -> Maybe (Gio.Callbacks.AsyncReadyCallback)
    
    
    -> m ()
iconInfoLoadSymbolicForContextAsync :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsIconInfo a, IsStyleContext b,
 IsCancellable c) =>
a -> b -> Maybe c -> Maybe AsyncReadyCallback -> m ()
iconInfoLoadSymbolicForContextAsync a
iconInfo b
context Maybe c
cancellable Maybe AsyncReadyCallback
callback = 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 IconInfo
iconInfo' <- a -> IO (Ptr IconInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iconInfo
    Ptr StyleContext
context' <- b -> IO (Ptr StyleContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
context
    Ptr Cancellable
maybeCancellable <- case Maybe c
cancellable of
        Maybe c
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just c
jCancellable -> do
            Ptr Cancellable
jCancellable' <- c -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
        Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just AsyncReadyCallback
jCallback -> do
            Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
            FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
            Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
            FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr IconInfo
-> Ptr StyleContext
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
gtk_icon_info_load_symbolic_for_context_async Ptr IconInfo
iconInfo' Ptr StyleContext
context' Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconInfo
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
context
    Maybe c -> (c -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe c
cancellable c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data IconInfoLoadSymbolicForContextAsyncMethodInfo
instance (signature ~ (b -> Maybe (c) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsIconInfo a, Gtk.StyleContext.IsStyleContext b, Gio.Cancellable.IsCancellable c) => O.OverloadedMethod IconInfoLoadSymbolicForContextAsyncMethodInfo a signature where
    overloadedMethod = iconInfoLoadSymbolicForContextAsync
instance O.OverloadedMethodInfo IconInfoLoadSymbolicForContextAsyncMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.IconInfo.iconInfoLoadSymbolicForContextAsync",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-IconInfo.html#v:iconInfoLoadSymbolicForContextAsync"
        }
#endif
foreign import ccall "gtk_icon_info_load_symbolic_for_context_finish" gtk_icon_info_load_symbolic_for_context_finish :: 
    Ptr IconInfo ->                         
    Ptr Gio.AsyncResult.AsyncResult ->      
    Ptr CInt ->                             
    Ptr (Ptr GError) ->                     
    IO (Ptr GdkPixbuf.Pixbuf.Pixbuf)
iconInfoLoadSymbolicForContextFinish ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconInfo a, Gio.AsyncResult.IsAsyncResult b) =>
    a
    
    -> b
    
    -> m ((GdkPixbuf.Pixbuf.Pixbuf, Bool))
    
    
    
    
iconInfoLoadSymbolicForContextFinish :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsIconInfo a, IsAsyncResult b) =>
a -> b -> m (Pixbuf, Bool)
iconInfoLoadSymbolicForContextFinish a
iconInfo b
res = IO (Pixbuf, Bool) -> m (Pixbuf, Bool)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Pixbuf, Bool) -> m (Pixbuf, Bool))
-> IO (Pixbuf, Bool) -> m (Pixbuf, Bool)
forall a b. (a -> b) -> a -> b
$ do
    Ptr IconInfo
iconInfo' <- a -> IO (Ptr IconInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iconInfo
    Ptr AsyncResult
res' <- b -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
res
    Ptr CInt
wasSymbolic <- IO (Ptr CInt)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CInt)
    IO (Pixbuf, Bool) -> IO () -> IO (Pixbuf, Bool)
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr Pixbuf
result <- (Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf))
-> (Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a b. (a -> b) -> a -> b
$ Ptr IconInfo
-> Ptr AsyncResult
-> Ptr CInt
-> Ptr (Ptr GError)
-> IO (Ptr Pixbuf)
gtk_icon_info_load_symbolic_for_context_finish Ptr IconInfo
iconInfo' Ptr AsyncResult
res' Ptr CInt
wasSymbolic
        Text -> Ptr Pixbuf -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iconInfoLoadSymbolicForContextFinish" Ptr Pixbuf
result
        Pixbuf
result' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Pixbuf -> Pixbuf
GdkPixbuf.Pixbuf.Pixbuf) Ptr Pixbuf
result
        CInt
wasSymbolic' <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
wasSymbolic
        let wasSymbolic'' :: Bool
wasSymbolic'' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
wasSymbolic'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconInfo
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
res
        Ptr CInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CInt
wasSymbolic
        (Pixbuf, Bool) -> IO (Pixbuf, Bool)
forall (m :: * -> *) a. Monad m => a -> m a
return (Pixbuf
result', Bool
wasSymbolic'')
     ) (do
        Ptr CInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CInt
wasSymbolic
     )
#if defined(ENABLE_OVERLOADING)
data IconInfoLoadSymbolicForContextFinishMethodInfo
instance (signature ~ (b -> m ((GdkPixbuf.Pixbuf.Pixbuf, Bool))), MonadIO m, IsIconInfo a, Gio.AsyncResult.IsAsyncResult b) => O.OverloadedMethod IconInfoLoadSymbolicForContextFinishMethodInfo a signature where
    overloadedMethod = iconInfoLoadSymbolicForContextFinish
instance O.OverloadedMethodInfo IconInfoLoadSymbolicForContextFinishMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.IconInfo.iconInfoLoadSymbolicForContextFinish",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-IconInfo.html#v:iconInfoLoadSymbolicForContextFinish"
        }
#endif
foreign import ccall "gtk_icon_info_load_symbolic_for_style" gtk_icon_info_load_symbolic_for_style :: 
    Ptr IconInfo ->                         
    Ptr Gtk.Style.Style ->                  
    CUInt ->                                
    Ptr CInt ->                             
    Ptr (Ptr GError) ->                     
    IO (Ptr GdkPixbuf.Pixbuf.Pixbuf)
{-# DEPRECATED iconInfoLoadSymbolicForStyle ["(Since version 3.0)","Use 'GI.Gtk.Objects.IconInfo.iconInfoLoadSymbolicForContext' instead"] #-}
iconInfoLoadSymbolicForStyle ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconInfo a, Gtk.Style.IsStyle b) =>
    a
    
    -> b
    
    -> Gtk.Enums.StateType
    
    -> m ((GdkPixbuf.Pixbuf.Pixbuf, Bool))
    
iconInfoLoadSymbolicForStyle :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsIconInfo a, IsStyle b) =>
a -> b -> StateType -> m (Pixbuf, Bool)
iconInfoLoadSymbolicForStyle a
iconInfo b
style StateType
state = IO (Pixbuf, Bool) -> m (Pixbuf, Bool)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Pixbuf, Bool) -> m (Pixbuf, Bool))
-> IO (Pixbuf, Bool) -> m (Pixbuf, Bool)
forall a b. (a -> b) -> a -> b
$ do
    Ptr IconInfo
iconInfo' <- a -> IO (Ptr IconInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iconInfo
    Ptr Style
style' <- b -> IO (Ptr Style)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
style
    let state' :: CUInt
state' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (StateType -> Int) -> StateType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StateType -> Int
forall a. Enum a => a -> Int
fromEnum) StateType
state
    Ptr CInt
wasSymbolic <- IO (Ptr CInt)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CInt)
    IO (Pixbuf, Bool) -> IO () -> IO (Pixbuf, Bool)
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr Pixbuf
result <- (Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf))
-> (Ptr (Ptr GError) -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a b. (a -> b) -> a -> b
$ Ptr IconInfo
-> Ptr Style
-> CUInt
-> Ptr CInt
-> Ptr (Ptr GError)
-> IO (Ptr Pixbuf)
gtk_icon_info_load_symbolic_for_style Ptr IconInfo
iconInfo' Ptr Style
style' CUInt
state' Ptr CInt
wasSymbolic
        Text -> Ptr Pixbuf -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iconInfoLoadSymbolicForStyle" Ptr Pixbuf
result
        Pixbuf
result' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Pixbuf -> Pixbuf
GdkPixbuf.Pixbuf.Pixbuf) Ptr Pixbuf
result
        CInt
wasSymbolic' <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
wasSymbolic
        let wasSymbolic'' :: Bool
wasSymbolic'' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
wasSymbolic'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconInfo
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
style
        Ptr CInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CInt
wasSymbolic
        (Pixbuf, Bool) -> IO (Pixbuf, Bool)
forall (m :: * -> *) a. Monad m => a -> m a
return (Pixbuf
result', Bool
wasSymbolic'')
     ) (do
        Ptr CInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CInt
wasSymbolic
     )
#if defined(ENABLE_OVERLOADING)
data IconInfoLoadSymbolicForStyleMethodInfo
instance (signature ~ (b -> Gtk.Enums.StateType -> m ((GdkPixbuf.Pixbuf.Pixbuf, Bool))), MonadIO m, IsIconInfo a, Gtk.Style.IsStyle b) => O.OverloadedMethod IconInfoLoadSymbolicForStyleMethodInfo a signature where
    overloadedMethod = iconInfoLoadSymbolicForStyle
instance O.OverloadedMethodInfo IconInfoLoadSymbolicForStyleMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.IconInfo.iconInfoLoadSymbolicForStyle",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-IconInfo.html#v:iconInfoLoadSymbolicForStyle"
        }
#endif
foreign import ccall "gtk_icon_info_set_raw_coordinates" gtk_icon_info_set_raw_coordinates :: 
    Ptr IconInfo ->                         
    CInt ->                                 
    IO ()
{-# DEPRECATED iconInfoSetRawCoordinates ["(Since version 3.14)","Embedded rectangles and attachment points are deprecated"] #-}
iconInfoSetRawCoordinates ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconInfo a) =>
    a
    
    -> Bool
    
    
    
    -> m ()
iconInfoSetRawCoordinates :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIconInfo a) =>
a -> Bool -> m ()
iconInfoSetRawCoordinates a
iconInfo Bool
rawCoordinates = 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 IconInfo
iconInfo' <- a -> IO (Ptr IconInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iconInfo
    let rawCoordinates' :: CInt
rawCoordinates' = (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
rawCoordinates
    Ptr IconInfo -> CInt -> IO ()
gtk_icon_info_set_raw_coordinates Ptr IconInfo
iconInfo' CInt
rawCoordinates'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconInfo
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data IconInfoSetRawCoordinatesMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsIconInfo a) => O.OverloadedMethod IconInfoSetRawCoordinatesMethodInfo a signature where
    overloadedMethod = iconInfoSetRawCoordinates
instance O.OverloadedMethodInfo IconInfoSetRawCoordinatesMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.IconInfo.iconInfoSetRawCoordinates",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-IconInfo.html#v:iconInfoSetRawCoordinates"
        }
#endif