{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Gtk.Objects.IconTheme.IconTheme' provides a facility for looking up icons by name
-- and size. The main reason for using a name rather than simply
-- providing a filename is to allow different icons to be used
-- depending on what “icon theme” is selected
-- by the user. The operation of icon themes on Linux and Unix
-- follows the <http://www.freedesktop.org/Standards/icon-theme-spec Icon Theme Specification>
-- There is a fallback icon theme, named @hicolor@, where applications
-- should install their icons, but additional icon themes can be installed
-- as operating system vendors and users choose.
-- 
-- Named icons are similar to the deprecated [Stock Items][gtkstock],
-- and the distinction between the two may be a bit confusing.
-- A few things to keep in mind:
-- 
-- * Stock images usually are used in conjunction with
-- [Stock Items][gtkstock], such as 'GI.Gtk.Constants.STOCK_OK' or
-- 'GI.Gtk.Constants.STOCK_OPEN'. Named icons are easier to set up and therefore
-- are more useful for new icons that an application wants to
-- add, such as application icons or window icons.
-- * Stock images can only be loaded at the symbolic sizes defined
-- by the t'GI.Gtk.Enums.IconSize' enumeration, or by custom sizes defined
-- by 'GI.Gtk.Functions.iconSizeRegister', while named icons are more flexible
-- and any pixel size can be specified.
-- * Because stock images are closely tied to stock items, and thus
-- to actions in the user interface, stock images may come in
-- multiple variants for different widget states or writing
-- directions.
-- 
-- 
-- A good rule of thumb is that if there is a stock image for what
-- you want to use, use it, otherwise use a named icon. It turns
-- out that internally stock images are generally defined in
-- terms of one or more named icons. (An example of the
-- more than one case is icons that depend on writing direction;
-- 'GI.Gtk.Constants.STOCK_GO_FORWARD' uses the two themed icons
-- “gtk-stock-go-forward-ltr” and “gtk-stock-go-forward-rtl”.)
-- 
-- In many cases, named themes are used indirectly, via t'GI.Gtk.Objects.Image.Image'
-- or stock items, rather than directly, but looking up icons
-- directly is also simple. The t'GI.Gtk.Objects.IconTheme.IconTheme' object acts
-- as a database of all the icons in the current theme. You
-- can create new t'GI.Gtk.Objects.IconTheme.IconTheme' objects, but it’s much more
-- efficient to use the standard icon theme for the t'GI.Gdk.Objects.Screen.Screen'
-- so that the icon information is shared with other people
-- looking up icons.
-- 
-- === /C code/
-- >
-- >GError *error = NULL;
-- >GtkIconTheme *icon_theme;
-- >GdkPixbuf *pixbuf;
-- >
-- >icon_theme = gtk_icon_theme_get_default ();
-- >pixbuf = gtk_icon_theme_load_icon (icon_theme,
-- >                                   "my-icon-name", // icon name
-- >                                   48, // icon size
-- >                                   0,  // flags
-- >                                   &error);
-- >if (!pixbuf)
-- >  {
-- >    g_warning ("Couldn’t load icon: %s", error->message);
-- >    g_error_free (error);
-- >  }
-- >else
-- >  {
-- >    // Use the pixbuf
-- >    g_object_unref (pixbuf);
-- >  }
-- 

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

module GI.Gtk.Objects.IconTheme
    ( 

-- * Exported types
    IconTheme(..)                           ,
    IsIconTheme                             ,
    toIconTheme                             ,
    noIconTheme                             ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveIconThemeMethod                  ,
#endif


-- ** addBuiltinIcon #method:addBuiltinIcon#

    iconThemeAddBuiltinIcon                 ,


-- ** addResourcePath #method:addResourcePath#

#if defined(ENABLE_OVERLOADING)
    IconThemeAddResourcePathMethodInfo      ,
#endif
    iconThemeAddResourcePath                ,


-- ** appendSearchPath #method:appendSearchPath#

#if defined(ENABLE_OVERLOADING)
    IconThemeAppendSearchPathMethodInfo     ,
#endif
    iconThemeAppendSearchPath               ,


-- ** chooseIcon #method:chooseIcon#

#if defined(ENABLE_OVERLOADING)
    IconThemeChooseIconMethodInfo           ,
#endif
    iconThemeChooseIcon                     ,


-- ** chooseIconForScale #method:chooseIconForScale#

#if defined(ENABLE_OVERLOADING)
    IconThemeChooseIconForScaleMethodInfo   ,
#endif
    iconThemeChooseIconForScale             ,


-- ** getDefault #method:getDefault#

    iconThemeGetDefault                     ,


-- ** getExampleIconName #method:getExampleIconName#

#if defined(ENABLE_OVERLOADING)
    IconThemeGetExampleIconNameMethodInfo   ,
#endif
    iconThemeGetExampleIconName             ,


-- ** getForScreen #method:getForScreen#

    iconThemeGetForScreen                   ,


-- ** getIconSizes #method:getIconSizes#

#if defined(ENABLE_OVERLOADING)
    IconThemeGetIconSizesMethodInfo         ,
#endif
    iconThemeGetIconSizes                   ,


-- ** getSearchPath #method:getSearchPath#

#if defined(ENABLE_OVERLOADING)
    IconThemeGetSearchPathMethodInfo        ,
#endif
    iconThemeGetSearchPath                  ,


-- ** hasIcon #method:hasIcon#

#if defined(ENABLE_OVERLOADING)
    IconThemeHasIconMethodInfo              ,
#endif
    iconThemeHasIcon                        ,


-- ** listContexts #method:listContexts#

#if defined(ENABLE_OVERLOADING)
    IconThemeListContextsMethodInfo         ,
#endif
    iconThemeListContexts                   ,


-- ** listIcons #method:listIcons#

#if defined(ENABLE_OVERLOADING)
    IconThemeListIconsMethodInfo            ,
#endif
    iconThemeListIcons                      ,


-- ** loadIcon #method:loadIcon#

#if defined(ENABLE_OVERLOADING)
    IconThemeLoadIconMethodInfo             ,
#endif
    iconThemeLoadIcon                       ,


-- ** loadIconForScale #method:loadIconForScale#

#if defined(ENABLE_OVERLOADING)
    IconThemeLoadIconForScaleMethodInfo     ,
#endif
    iconThemeLoadIconForScale               ,


-- ** loadSurface #method:loadSurface#

#if defined(ENABLE_OVERLOADING)
    IconThemeLoadSurfaceMethodInfo          ,
#endif
    iconThemeLoadSurface                    ,


-- ** lookupByGicon #method:lookupByGicon#

#if defined(ENABLE_OVERLOADING)
    IconThemeLookupByGiconMethodInfo        ,
#endif
    iconThemeLookupByGicon                  ,


-- ** lookupByGiconForScale #method:lookupByGiconForScale#

#if defined(ENABLE_OVERLOADING)
    IconThemeLookupByGiconForScaleMethodInfo,
#endif
    iconThemeLookupByGiconForScale          ,


-- ** lookupIcon #method:lookupIcon#

#if defined(ENABLE_OVERLOADING)
    IconThemeLookupIconMethodInfo           ,
#endif
    iconThemeLookupIcon                     ,


-- ** lookupIconForScale #method:lookupIconForScale#

#if defined(ENABLE_OVERLOADING)
    IconThemeLookupIconForScaleMethodInfo   ,
#endif
    iconThemeLookupIconForScale             ,


-- ** new #method:new#

    iconThemeNew                            ,


-- ** prependSearchPath #method:prependSearchPath#

#if defined(ENABLE_OVERLOADING)
    IconThemePrependSearchPathMethodInfo    ,
#endif
    iconThemePrependSearchPath              ,


-- ** rescanIfNeeded #method:rescanIfNeeded#

#if defined(ENABLE_OVERLOADING)
    IconThemeRescanIfNeededMethodInfo       ,
#endif
    iconThemeRescanIfNeeded                 ,


-- ** setCustomTheme #method:setCustomTheme#

#if defined(ENABLE_OVERLOADING)
    IconThemeSetCustomThemeMethodInfo       ,
#endif
    iconThemeSetCustomTheme                 ,


-- ** setScreen #method:setScreen#

#if defined(ENABLE_OVERLOADING)
    IconThemeSetScreenMethodInfo            ,
#endif
    iconThemeSetScreen                      ,


-- ** setSearchPath #method:setSearchPath#

#if defined(ENABLE_OVERLOADING)
    IconThemeSetSearchPathMethodInfo        ,
#endif
    iconThemeSetSearchPath                  ,




 -- * Signals
-- ** changed #signal:changed#

    C_IconThemeChangedCallback              ,
    IconThemeChangedCallback                ,
#if defined(ENABLE_OVERLOADING)
    IconThemeChangedSignalInfo              ,
#endif
    afterIconThemeChanged                   ,
    genClosure_IconThemeChanged             ,
    mk_IconThemeChangedCallback             ,
    noIconThemeChangedCallback              ,
    onIconThemeChanged                      ,
    wrap_IconThemeChangedCallback           ,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL

import qualified GI.Cairo.Structs.Surface as Cairo.Surface
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Objects.Screen as Gdk.Screen
import qualified GI.Gdk.Objects.Window as Gdk.Window
import qualified GI.GdkPixbuf.Objects.Pixbuf as GdkPixbuf.Pixbuf
import qualified GI.Gio.Interfaces.Icon as Gio.Icon
import {-# SOURCE #-} qualified GI.Gtk.Flags as Gtk.Flags
import {-# SOURCE #-} qualified GI.Gtk.Objects.IconInfo as Gtk.IconInfo

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

instance GObject IconTheme where
    gobjectType :: IO GType
gobjectType = IO GType
c_gtk_icon_theme_get_type
    

-- | Convert 'IconTheme' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue IconTheme where
    toGValue :: IconTheme -> IO GValue
toGValue o :: IconTheme
o = do
        GType
gtype <- IO GType
c_gtk_icon_theme_get_type
        IconTheme -> (Ptr IconTheme -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr IconTheme
o (GType
-> (GValue -> Ptr IconTheme -> IO ()) -> Ptr IconTheme -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr IconTheme -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO IconTheme
fromGValue gv :: GValue
gv = do
        Ptr IconTheme
ptr <- GValue -> IO (Ptr IconTheme)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr IconTheme)
        (ManagedPtr IconTheme -> IconTheme)
-> Ptr IconTheme -> IO IconTheme
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr IconTheme -> IconTheme
IconTheme Ptr IconTheme
ptr
        
    

-- | Type class for types which can be safely cast to `IconTheme`, for instance with `toIconTheme`.
class (GObject o, O.IsDescendantOf IconTheme o) => IsIconTheme o
instance (GObject o, O.IsDescendantOf IconTheme o) => IsIconTheme o

instance O.HasParentTypes IconTheme
type instance O.ParentTypes IconTheme = '[GObject.Object.Object]

-- | Cast to `IconTheme`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toIconTheme :: (MonadIO m, IsIconTheme o) => o -> m IconTheme
toIconTheme :: o -> m IconTheme
toIconTheme = IO IconTheme -> m IconTheme
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO IconTheme -> m IconTheme)
-> (o -> IO IconTheme) -> o -> m IconTheme
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr IconTheme -> IconTheme) -> o -> IO IconTheme
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr IconTheme -> IconTheme
IconTheme

-- | A convenience alias for `Nothing` :: `Maybe` `IconTheme`.
noIconTheme :: Maybe IconTheme
noIconTheme :: Maybe IconTheme
noIconTheme = Maybe IconTheme
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveIconThemeMethod (t :: Symbol) (o :: *) :: * where
    ResolveIconThemeMethod "addResourcePath" o = IconThemeAddResourcePathMethodInfo
    ResolveIconThemeMethod "appendSearchPath" o = IconThemeAppendSearchPathMethodInfo
    ResolveIconThemeMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveIconThemeMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveIconThemeMethod "chooseIcon" o = IconThemeChooseIconMethodInfo
    ResolveIconThemeMethod "chooseIconForScale" o = IconThemeChooseIconForScaleMethodInfo
    ResolveIconThemeMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveIconThemeMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveIconThemeMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveIconThemeMethod "hasIcon" o = IconThemeHasIconMethodInfo
    ResolveIconThemeMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveIconThemeMethod "listContexts" o = IconThemeListContextsMethodInfo
    ResolveIconThemeMethod "listIcons" o = IconThemeListIconsMethodInfo
    ResolveIconThemeMethod "loadIcon" o = IconThemeLoadIconMethodInfo
    ResolveIconThemeMethod "loadIconForScale" o = IconThemeLoadIconForScaleMethodInfo
    ResolveIconThemeMethod "loadSurface" o = IconThemeLoadSurfaceMethodInfo
    ResolveIconThemeMethod "lookupByGicon" o = IconThemeLookupByGiconMethodInfo
    ResolveIconThemeMethod "lookupByGiconForScale" o = IconThemeLookupByGiconForScaleMethodInfo
    ResolveIconThemeMethod "lookupIcon" o = IconThemeLookupIconMethodInfo
    ResolveIconThemeMethod "lookupIconForScale" o = IconThemeLookupIconForScaleMethodInfo
    ResolveIconThemeMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveIconThemeMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveIconThemeMethod "prependSearchPath" o = IconThemePrependSearchPathMethodInfo
    ResolveIconThemeMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveIconThemeMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveIconThemeMethod "rescanIfNeeded" o = IconThemeRescanIfNeededMethodInfo
    ResolveIconThemeMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveIconThemeMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveIconThemeMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveIconThemeMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveIconThemeMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveIconThemeMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveIconThemeMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveIconThemeMethod "getExampleIconName" o = IconThemeGetExampleIconNameMethodInfo
    ResolveIconThemeMethod "getIconSizes" o = IconThemeGetIconSizesMethodInfo
    ResolveIconThemeMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveIconThemeMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveIconThemeMethod "getSearchPath" o = IconThemeGetSearchPathMethodInfo
    ResolveIconThemeMethod "setCustomTheme" o = IconThemeSetCustomThemeMethodInfo
    ResolveIconThemeMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveIconThemeMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveIconThemeMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveIconThemeMethod "setScreen" o = IconThemeSetScreenMethodInfo
    ResolveIconThemeMethod "setSearchPath" o = IconThemeSetSearchPathMethodInfo
    ResolveIconThemeMethod l o = O.MethodResolutionFailed l o

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

#endif

-- signal IconTheme::changed
-- | Emitted when the current icon theme is switched or GTK+ detects
-- that a change has occurred in the contents of the current
-- icon theme.
type IconThemeChangedCallback =
    IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `IconThemeChangedCallback`@.
noIconThemeChangedCallback :: Maybe IconThemeChangedCallback
noIconThemeChangedCallback :: Maybe (IO ())
noIconThemeChangedCallback = Maybe (IO ())
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_IconThemeChangedCallback =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_IconThemeChangedCallback`.
foreign import ccall "wrapper"
    mk_IconThemeChangedCallback :: C_IconThemeChangedCallback -> IO (FunPtr C_IconThemeChangedCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_IconThemeChanged :: MonadIO m => IconThemeChangedCallback -> m (GClosure C_IconThemeChangedCallback)
genClosure_IconThemeChanged :: IO () -> m (GClosure C_IconThemeChangedCallback)
genClosure_IconThemeChanged cb :: IO ()
cb = IO (GClosure C_IconThemeChangedCallback)
-> m (GClosure C_IconThemeChangedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_IconThemeChangedCallback)
 -> m (GClosure C_IconThemeChangedCallback))
-> IO (GClosure C_IconThemeChangedCallback)
-> m (GClosure C_IconThemeChangedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_IconThemeChangedCallback
cb' = IO () -> C_IconThemeChangedCallback
wrap_IconThemeChangedCallback IO ()
cb
    C_IconThemeChangedCallback
-> IO (FunPtr C_IconThemeChangedCallback)
mk_IconThemeChangedCallback C_IconThemeChangedCallback
cb' IO (FunPtr C_IconThemeChangedCallback)
-> (FunPtr C_IconThemeChangedCallback
    -> IO (GClosure C_IconThemeChangedCallback))
-> IO (GClosure C_IconThemeChangedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_IconThemeChangedCallback
-> IO (GClosure C_IconThemeChangedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `IconThemeChangedCallback` into a `C_IconThemeChangedCallback`.
wrap_IconThemeChangedCallback ::
    IconThemeChangedCallback ->
    C_IconThemeChangedCallback
wrap_IconThemeChangedCallback :: IO () -> C_IconThemeChangedCallback
wrap_IconThemeChangedCallback _cb :: IO ()
_cb _ _ = do
    IO ()
_cb 


-- | Connect a signal handler for the [changed](#signal:changed) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' iconTheme #changed callback
-- @
-- 
-- 
onIconThemeChanged :: (IsIconTheme a, MonadIO m) => a -> IconThemeChangedCallback -> m SignalHandlerId
onIconThemeChanged :: a -> IO () -> m SignalHandlerId
onIconThemeChanged obj :: a
obj cb :: IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_IconThemeChangedCallback
cb' = IO () -> C_IconThemeChangedCallback
wrap_IconThemeChangedCallback IO ()
cb
    FunPtr C_IconThemeChangedCallback
cb'' <- C_IconThemeChangedCallback
-> IO (FunPtr C_IconThemeChangedCallback)
mk_IconThemeChangedCallback C_IconThemeChangedCallback
cb'
    a
-> Text
-> FunPtr C_IconThemeChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "changed" FunPtr C_IconThemeChangedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [changed](#signal:changed) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' iconTheme #changed callback
-- @
-- 
-- 
afterIconThemeChanged :: (IsIconTheme a, MonadIO m) => a -> IconThemeChangedCallback -> m SignalHandlerId
afterIconThemeChanged :: a -> IO () -> m SignalHandlerId
afterIconThemeChanged obj :: a
obj cb :: IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_IconThemeChangedCallback
cb' = IO () -> C_IconThemeChangedCallback
wrap_IconThemeChangedCallback IO ()
cb
    FunPtr C_IconThemeChangedCallback
cb'' <- C_IconThemeChangedCallback
-> IO (FunPtr C_IconThemeChangedCallback)
mk_IconThemeChangedCallback C_IconThemeChangedCallback
cb'
    a
-> Text
-> FunPtr C_IconThemeChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "changed" FunPtr C_IconThemeChangedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data IconThemeChangedSignalInfo
instance SignalInfo IconThemeChangedSignalInfo where
    type HaskellCallbackType IconThemeChangedSignalInfo = IconThemeChangedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_IconThemeChangedCallback cb
        cb'' <- mk_IconThemeChangedCallback cb'
        connectSignalFunPtr obj "changed" cb'' connectMode detail

#endif

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

#if defined(ENABLE_OVERLOADING)
#endif

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

#endif

-- method IconTheme::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "IconTheme" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_icon_theme_new" gtk_icon_theme_new :: 
    IO (Ptr IconTheme)

-- | Creates a new icon theme object. Icon theme objects are used
-- to lookup up an icon by name in a particular icon theme.
-- Usually, you’ll want to use 'GI.Gtk.Objects.IconTheme.iconThemeGetDefault'
-- or 'GI.Gtk.Objects.IconTheme.iconThemeGetForScreen' rather than creating
-- a new icon theme object for scratch.
-- 
-- /Since: 2.4/
iconThemeNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m IconTheme
    -- ^ __Returns:__ the newly created t'GI.Gtk.Objects.IconTheme.IconTheme' object.
iconThemeNew :: m IconTheme
iconThemeNew  = IO IconTheme -> m IconTheme
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO IconTheme -> m IconTheme) -> IO IconTheme -> m IconTheme
forall a b. (a -> b) -> a -> b
$ do
    Ptr IconTheme
result <- IO (Ptr IconTheme)
gtk_icon_theme_new
    Text -> Ptr IconTheme -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "iconThemeNew" Ptr IconTheme
result
    IconTheme
result' <- ((ManagedPtr IconTheme -> IconTheme)
-> Ptr IconTheme -> IO IconTheme
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr IconTheme -> IconTheme
IconTheme) Ptr IconTheme
result
    IconTheme -> IO IconTheme
forall (m :: * -> *) a. Monad m => a -> m a
return IconTheme
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method IconTheme::add_resource_path
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "icon_theme"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IconTheme" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkIconTheme" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a resource path" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_icon_theme_add_resource_path" gtk_icon_theme_add_resource_path :: 
    Ptr IconTheme ->                        -- icon_theme : TInterface (Name {namespace = "Gtk", name = "IconTheme"})
    CString ->                              -- path : TBasicType TUTF8
    IO ()

-- | Adds a resource path that will be looked at when looking
-- for icons, similar to search paths.
-- 
-- This function should be used to make application-specific icons
-- available as part of the icon theme.
-- 
-- The resources are considered as part of the hicolor icon theme
-- and must be located in subdirectories that are defined in the
-- hicolor icon theme, such as @\@path\/16x16\/actions\/run.png@.
-- Icons that are directly placed in the resource path instead
-- of a subdirectory are also considered as ultimate fallback.
-- 
-- /Since: 3.14/
iconThemeAddResourcePath ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
    a
    -- ^ /@iconTheme@/: a t'GI.Gtk.Objects.IconTheme.IconTheme'
    -> T.Text
    -- ^ /@path@/: a resource path
    -> m ()
iconThemeAddResourcePath :: a -> Text -> m ()
iconThemeAddResourcePath iconTheme :: a
iconTheme path :: Text
path = 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 IconTheme
iconTheme' <- a -> IO (Ptr IconTheme)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iconTheme
    CString
path' <- Text -> IO CString
textToCString Text
path
    Ptr IconTheme -> CString -> IO ()
gtk_icon_theme_add_resource_path Ptr IconTheme
iconTheme' CString
path'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconTheme
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data IconThemeAddResourcePathMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsIconTheme a) => O.MethodInfo IconThemeAddResourcePathMethodInfo a signature where
    overloadedMethod = iconThemeAddResourcePath

#endif

-- method IconTheme::append_search_path
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "icon_theme"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IconTheme" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkIconTheme" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "path"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "directory name to append to the icon path"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_icon_theme_append_search_path" gtk_icon_theme_append_search_path :: 
    Ptr IconTheme ->                        -- icon_theme : TInterface (Name {namespace = "Gtk", name = "IconTheme"})
    CString ->                              -- path : TBasicType TFileName
    IO ()

-- | Appends a directory to the search path.
-- See 'GI.Gtk.Objects.IconTheme.iconThemeSetSearchPath'.
-- 
-- /Since: 2.4/
iconThemeAppendSearchPath ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
    a
    -- ^ /@iconTheme@/: a t'GI.Gtk.Objects.IconTheme.IconTheme'
    -> [Char]
    -- ^ /@path@/: directory name to append to the icon path
    -> m ()
iconThemeAppendSearchPath :: a -> [Char] -> m ()
iconThemeAppendSearchPath iconTheme :: a
iconTheme path :: [Char]
path = 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 IconTheme
iconTheme' <- a -> IO (Ptr IconTheme)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iconTheme
    CString
path' <- [Char] -> IO CString
stringToCString [Char]
path
    Ptr IconTheme -> CString -> IO ()
gtk_icon_theme_append_search_path Ptr IconTheme
iconTheme' CString
path'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconTheme
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data IconThemeAppendSearchPathMethodInfo
instance (signature ~ ([Char] -> m ()), MonadIO m, IsIconTheme a) => O.MethodInfo IconThemeAppendSearchPathMethodInfo a signature where
    overloadedMethod = iconThemeAppendSearchPath

#endif

-- method IconTheme::choose_icon
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "icon_theme"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IconTheme" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkIconTheme" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "icon_names"
--           , argType = TCArray True (-1) (-1) (TBasicType TUTF8)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "%NULL-terminated array of\n    icon names to lookup"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "desired icon size" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IconLookupFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "flags modifying the behavior of the icon lookup"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "IconInfo" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_icon_theme_choose_icon" gtk_icon_theme_choose_icon :: 
    Ptr IconTheme ->                        -- icon_theme : TInterface (Name {namespace = "Gtk", name = "IconTheme"})
    Ptr CString ->                          -- icon_names : TCArray True (-1) (-1) (TBasicType TUTF8)
    Int32 ->                                -- size : TBasicType TInt
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gtk", name = "IconLookupFlags"})
    IO (Ptr Gtk.IconInfo.IconInfo)

-- | Looks up a named icon and returns a t'GI.Gtk.Objects.IconInfo.IconInfo' containing
-- information such as the filename of the icon. The icon
-- can then be rendered into a pixbuf using
-- 'GI.Gtk.Objects.IconInfo.iconInfoLoadIcon'. ('GI.Gtk.Objects.IconTheme.iconThemeLoadIcon'
-- combines these two steps if all you need is the pixbuf.)
-- 
-- If /@iconNames@/ contains more than one name, this function
-- tries them all in the given order before falling back to
-- inherited icon themes.
-- 
-- /Since: 2.12/
iconThemeChooseIcon ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
    a
    -- ^ /@iconTheme@/: a t'GI.Gtk.Objects.IconTheme.IconTheme'
    -> [T.Text]
    -- ^ /@iconNames@/: 'P.Nothing'-terminated array of
    --     icon names to lookup
    -> Int32
    -- ^ /@size@/: desired icon size
    -> [Gtk.Flags.IconLookupFlags]
    -- ^ /@flags@/: flags modifying the behavior of the icon lookup
    -> m (Maybe Gtk.IconInfo.IconInfo)
    -- ^ __Returns:__ a t'GI.Gtk.Objects.IconInfo.IconInfo' object
    -- containing information about the icon, or 'P.Nothing' if the icon wasn’t
    -- found.
iconThemeChooseIcon :: a -> [Text] -> Int32 -> [IconLookupFlags] -> m (Maybe IconInfo)
iconThemeChooseIcon iconTheme :: a
iconTheme iconNames :: [Text]
iconNames size :: Int32
size flags :: [IconLookupFlags]
flags = IO (Maybe IconInfo) -> m (Maybe IconInfo)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe IconInfo) -> m (Maybe IconInfo))
-> IO (Maybe IconInfo) -> m (Maybe 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 CString
iconNames' <- [Text] -> IO (Ptr CString)
packZeroTerminatedUTF8CArray [Text]
iconNames
    let flags' :: CUInt
flags' = [IconLookupFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [IconLookupFlags]
flags
    Ptr IconInfo
result <- Ptr IconTheme -> Ptr CString -> Int32 -> CUInt -> IO (Ptr IconInfo)
gtk_icon_theme_choose_icon Ptr IconTheme
iconTheme' Ptr CString
iconNames' Int32
size CUInt
flags'
    Maybe IconInfo
maybeResult <- Ptr IconInfo
-> (Ptr IconInfo -> IO IconInfo) -> IO (Maybe IconInfo)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr IconInfo
result ((Ptr IconInfo -> IO IconInfo) -> IO (Maybe IconInfo))
-> (Ptr IconInfo -> IO IconInfo) -> IO (Maybe IconInfo)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr IconInfo
result' -> do
        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
Gtk.IconInfo.IconInfo) Ptr IconInfo
result'
        IconInfo -> IO IconInfo
forall (m :: * -> *) a. Monad m => a -> m a
return IconInfo
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconTheme
    (CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
iconNames'
    Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
iconNames'
    Maybe IconInfo -> IO (Maybe IconInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe IconInfo
maybeResult

#if defined(ENABLE_OVERLOADING)
data IconThemeChooseIconMethodInfo
instance (signature ~ ([T.Text] -> Int32 -> [Gtk.Flags.IconLookupFlags] -> m (Maybe Gtk.IconInfo.IconInfo)), MonadIO m, IsIconTheme a) => O.MethodInfo IconThemeChooseIconMethodInfo a signature where
    overloadedMethod = iconThemeChooseIcon

#endif

-- method IconTheme::choose_icon_for_scale
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "icon_theme"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IconTheme" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkIconTheme" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "icon_names"
--           , argType = TCArray True (-1) (-1) (TBasicType TUTF8)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "%NULL-terminated\n    array of icon names to lookup"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "desired icon size" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "scale"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "desired scale" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IconLookupFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "flags modifying the behavior of the icon lookup"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "IconInfo" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_icon_theme_choose_icon_for_scale" gtk_icon_theme_choose_icon_for_scale :: 
    Ptr IconTheme ->                        -- icon_theme : TInterface (Name {namespace = "Gtk", name = "IconTheme"})
    Ptr CString ->                          -- icon_names : TCArray True (-1) (-1) (TBasicType TUTF8)
    Int32 ->                                -- size : TBasicType TInt
    Int32 ->                                -- scale : TBasicType TInt
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gtk", name = "IconLookupFlags"})
    IO (Ptr Gtk.IconInfo.IconInfo)

-- | Looks up a named icon for a particular window scale and returns
-- a t'GI.Gtk.Objects.IconInfo.IconInfo' containing information such as the filename of the
-- icon. The icon can then be rendered into a pixbuf using
-- 'GI.Gtk.Objects.IconInfo.iconInfoLoadIcon'. ('GI.Gtk.Objects.IconTheme.iconThemeLoadIcon'
-- combines these two steps if all you need is the pixbuf.)
-- 
-- If /@iconNames@/ contains more than one name, this function
-- tries them all in the given order before falling back to
-- inherited icon themes.
-- 
-- /Since: 3.10/
iconThemeChooseIconForScale ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
    a
    -- ^ /@iconTheme@/: a t'GI.Gtk.Objects.IconTheme.IconTheme'
    -> [T.Text]
    -- ^ /@iconNames@/: 'P.Nothing'-terminated
    --     array of icon names to lookup
    -> Int32
    -- ^ /@size@/: desired icon size
    -> Int32
    -- ^ /@scale@/: desired scale
    -> [Gtk.Flags.IconLookupFlags]
    -- ^ /@flags@/: flags modifying the behavior of the icon lookup
    -> m (Maybe Gtk.IconInfo.IconInfo)
    -- ^ __Returns:__ a t'GI.Gtk.Objects.IconInfo.IconInfo' object
    --     containing information about the icon, or 'P.Nothing' if the
    --     icon wasn’t found.
iconThemeChooseIconForScale :: a
-> [Text]
-> Int32
-> Int32
-> [IconLookupFlags]
-> m (Maybe IconInfo)
iconThemeChooseIconForScale iconTheme :: a
iconTheme iconNames :: [Text]
iconNames size :: Int32
size scale :: Int32
scale flags :: [IconLookupFlags]
flags = IO (Maybe IconInfo) -> m (Maybe IconInfo)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe IconInfo) -> m (Maybe IconInfo))
-> IO (Maybe IconInfo) -> m (Maybe 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 CString
iconNames' <- [Text] -> IO (Ptr CString)
packZeroTerminatedUTF8CArray [Text]
iconNames
    let flags' :: CUInt
flags' = [IconLookupFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [IconLookupFlags]
flags
    Ptr IconInfo
result <- Ptr IconTheme
-> Ptr CString -> Int32 -> Int32 -> CUInt -> IO (Ptr IconInfo)
gtk_icon_theme_choose_icon_for_scale Ptr IconTheme
iconTheme' Ptr CString
iconNames' Int32
size Int32
scale CUInt
flags'
    Maybe IconInfo
maybeResult <- Ptr IconInfo
-> (Ptr IconInfo -> IO IconInfo) -> IO (Maybe IconInfo)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr IconInfo
result ((Ptr IconInfo -> IO IconInfo) -> IO (Maybe IconInfo))
-> (Ptr IconInfo -> IO IconInfo) -> IO (Maybe IconInfo)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr IconInfo
result' -> do
        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
Gtk.IconInfo.IconInfo) Ptr IconInfo
result'
        IconInfo -> IO IconInfo
forall (m :: * -> *) a. Monad m => a -> m a
return IconInfo
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconTheme
    (CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
iconNames'
    Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
iconNames'
    Maybe IconInfo -> IO (Maybe IconInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe IconInfo
maybeResult

#if defined(ENABLE_OVERLOADING)
data IconThemeChooseIconForScaleMethodInfo
instance (signature ~ ([T.Text] -> Int32 -> Int32 -> [Gtk.Flags.IconLookupFlags] -> m (Maybe Gtk.IconInfo.IconInfo)), MonadIO m, IsIconTheme a) => O.MethodInfo IconThemeChooseIconForScaleMethodInfo a signature where
    overloadedMethod = iconThemeChooseIconForScale

#endif

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

foreign import ccall "gtk_icon_theme_get_example_icon_name" gtk_icon_theme_get_example_icon_name :: 
    Ptr IconTheme ->                        -- icon_theme : TInterface (Name {namespace = "Gtk", name = "IconTheme"})
    IO CString

-- | Gets the name of an icon that is representative of the
-- current theme (for instance, to use when presenting
-- a list of themes to the user.)
-- 
-- /Since: 2.4/
iconThemeGetExampleIconName ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
    a
    -- ^ /@iconTheme@/: a t'GI.Gtk.Objects.IconTheme.IconTheme'
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the name of an example icon or 'P.Nothing'.
    --     Free with 'GI.GLib.Functions.free'.
iconThemeGetExampleIconName :: a -> m (Maybe Text)
iconThemeGetExampleIconName iconTheme :: a
iconTheme = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
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
    CString
result <- Ptr IconTheme -> IO CString
gtk_icon_theme_get_example_icon_name Ptr IconTheme
iconTheme'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \result' :: CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconTheme
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data IconThemeGetExampleIconNameMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsIconTheme a) => O.MethodInfo IconThemeGetExampleIconNameMethodInfo a signature where
    overloadedMethod = iconThemeGetExampleIconName

#endif

-- method IconTheme::get_icon_sizes
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "icon_theme"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IconTheme" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkIconTheme" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "icon_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of an icon"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TCArray True (-1) (-1) (TBasicType TInt))
-- throws : False
-- Skip return : False

foreign import ccall "gtk_icon_theme_get_icon_sizes" gtk_icon_theme_get_icon_sizes :: 
    Ptr IconTheme ->                        -- icon_theme : TInterface (Name {namespace = "Gtk", name = "IconTheme"})
    CString ->                              -- icon_name : TBasicType TUTF8
    IO (Ptr Int32)

-- | Returns an array of integers describing the sizes at which
-- the icon is available without scaling. A size of -1 means
-- that the icon is available in a scalable format. The array
-- is zero-terminated.
-- 
-- /Since: 2.6/
iconThemeGetIconSizes ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
    a
    -- ^ /@iconTheme@/: a t'GI.Gtk.Objects.IconTheme.IconTheme'
    -> T.Text
    -- ^ /@iconName@/: the name of an icon
    -> m [Int32]
    -- ^ __Returns:__ An newly
    -- allocated array describing the sizes at which the icon is
    -- available. The array should be freed with 'GI.GLib.Functions.free' when it is no
    -- longer needed.
iconThemeGetIconSizes :: a -> Text -> m [Int32]
iconThemeGetIconSizes iconTheme :: a
iconTheme iconName :: Text
iconName = 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 IconTheme
iconTheme' <- a -> IO (Ptr IconTheme)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iconTheme
    CString
iconName' <- Text -> IO CString
textToCString Text
iconName
    Ptr Int32
result <- Ptr IconTheme -> CString -> IO (Ptr Int32)
gtk_icon_theme_get_icon_sizes Ptr IconTheme
iconTheme' CString
iconName'
    Text -> Ptr Int32 -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "iconThemeGetIconSizes" Ptr Int32
result
    [Int32]
result' <- Ptr Int32 -> IO [Int32]
forall a. (Eq a, Num a, Storable a) => Ptr a -> IO [a]
unpackZeroTerminatedStorableArray Ptr Int32
result
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconTheme
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
iconName'
    [Int32] -> IO [Int32]
forall (m :: * -> *) a. Monad m => a -> m a
return [Int32]
result'

#if defined(ENABLE_OVERLOADING)
data IconThemeGetIconSizesMethodInfo
instance (signature ~ (T.Text -> m [Int32]), MonadIO m, IsIconTheme a) => O.MethodInfo IconThemeGetIconSizesMethodInfo a signature where
    overloadedMethod = iconThemeGetIconSizes

#endif

-- method IconTheme::get_search_path
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "icon_theme"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IconTheme" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkIconTheme" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "path"
--           , argType = TCArray False (-1) 2 (TBasicType TFileName)
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "\n    location to store a list of icon theme path directories or %NULL.\n    The stored value should be freed with g_strfreev()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "n_elements"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "location to store number of elements in @path, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "n_elements"
--              , argType = TBasicType TInt
--              , direction = DirectionOut
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText =
--                        Just "location to store number of elements in @path, or %NULL"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferEverything
--              }
--          ]
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_icon_theme_get_search_path" gtk_icon_theme_get_search_path :: 
    Ptr IconTheme ->                        -- icon_theme : TInterface (Name {namespace = "Gtk", name = "IconTheme"})
    Ptr (Ptr CString) ->                    -- path : TCArray False (-1) 2 (TBasicType TFileName)
    Ptr Int32 ->                            -- n_elements : TBasicType TInt
    IO ()

-- | Gets the current search path. See 'GI.Gtk.Objects.IconTheme.iconThemeSetSearchPath'.
-- 
-- /Since: 2.4/
iconThemeGetSearchPath ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
    a
    -- ^ /@iconTheme@/: a t'GI.Gtk.Objects.IconTheme.IconTheme'
    -> m ([[Char]])
iconThemeGetSearchPath :: a -> m [[Char]]
iconThemeGetSearchPath iconTheme :: a
iconTheme = IO [[Char]] -> m [[Char]]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [[Char]] -> m [[Char]]) -> IO [[Char]] -> m [[Char]]
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 (Ptr CString)
path <- IO (Ptr (Ptr CString))
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr (Ptr CString))
    Ptr Int32
nElements <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr IconTheme -> Ptr (Ptr CString) -> Ptr Int32 -> IO ()
gtk_icon_theme_get_search_path Ptr IconTheme
iconTheme' Ptr (Ptr CString)
path Ptr Int32
nElements
    Int32
nElements' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
nElements
    Ptr CString
path' <- Ptr (Ptr CString) -> IO (Ptr CString)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr CString)
path
    [[Char]]
path'' <- (Int32 -> Ptr CString -> IO [[Char]]
forall a.
(HasCallStack, Integral a) =>
a -> Ptr CString -> IO [[Char]]
unpackFileNameArrayWithLength Int32
nElements') Ptr CString
path'
    (Int32 -> (CString -> IO ()) -> Ptr CString -> IO ()
forall a b c.
(Storable a, Integral b) =>
b -> (a -> IO c) -> Ptr a -> IO ()
mapCArrayWithLength Int32
nElements') CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
path'
    Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
path'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconTheme
    Ptr (Ptr CString) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr CString)
path
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
nElements
    [[Char]] -> IO [[Char]]
forall (m :: * -> *) a. Monad m => a -> m a
return [[Char]]
path''

#if defined(ENABLE_OVERLOADING)
data IconThemeGetSearchPathMethodInfo
instance (signature ~ (m ([[Char]])), MonadIO m, IsIconTheme a) => O.MethodInfo IconThemeGetSearchPathMethodInfo a signature where
    overloadedMethod = iconThemeGetSearchPath

#endif

-- method IconTheme::has_icon
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "icon_theme"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IconTheme" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkIconTheme" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "icon_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of an icon"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_icon_theme_has_icon" gtk_icon_theme_has_icon :: 
    Ptr IconTheme ->                        -- icon_theme : TInterface (Name {namespace = "Gtk", name = "IconTheme"})
    CString ->                              -- icon_name : TBasicType TUTF8
    IO CInt

-- | Checks whether an icon theme includes an icon
-- for a particular name.
-- 
-- /Since: 2.4/
iconThemeHasIcon ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
    a
    -- ^ /@iconTheme@/: a t'GI.Gtk.Objects.IconTheme.IconTheme'
    -> T.Text
    -- ^ /@iconName@/: the name of an icon
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@iconTheme@/ includes an
    --  icon for /@iconName@/.
iconThemeHasIcon :: a -> Text -> m Bool
iconThemeHasIcon iconTheme :: a
iconTheme iconName :: Text
iconName = 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 IconTheme
iconTheme' <- a -> IO (Ptr IconTheme)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iconTheme
    CString
iconName' <- Text -> IO CString
textToCString Text
iconName
    CInt
result <- Ptr IconTheme -> CString -> IO CInt
gtk_icon_theme_has_icon Ptr IconTheme
iconTheme' CString
iconName'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconTheme
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
iconName'
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data IconThemeHasIconMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m, IsIconTheme a) => O.MethodInfo IconThemeHasIconMethodInfo a signature where
    overloadedMethod = iconThemeHasIcon

#endif

-- method IconTheme::list_contexts
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "icon_theme"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IconTheme" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkIconTheme" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TGList (TBasicType TUTF8))
-- throws : False
-- Skip return : False

foreign import ccall "gtk_icon_theme_list_contexts" gtk_icon_theme_list_contexts :: 
    Ptr IconTheme ->                        -- icon_theme : TInterface (Name {namespace = "Gtk", name = "IconTheme"})
    IO (Ptr (GList CString))

-- | Gets the list of contexts available within the current
-- hierarchy of icon themes.
-- See 'GI.Gtk.Objects.IconTheme.iconThemeListIcons' for details about contexts.
-- 
-- /Since: 2.12/
iconThemeListContexts ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
    a
    -- ^ /@iconTheme@/: a t'GI.Gtk.Objects.IconTheme.IconTheme'
    -> m [T.Text]
    -- ^ __Returns:__ a t'GI.GLib.Structs.List.List' list
    --     holding the names of all the contexts in the theme. You must first
    --     free each element in the list with 'GI.GLib.Functions.free', then free the list
    --     itself with @/g_list_free()/@.
iconThemeListContexts :: a -> m [Text]
iconThemeListContexts iconTheme :: a
iconTheme = 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 IconTheme
iconTheme' <- a -> IO (Ptr IconTheme)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iconTheme
    Ptr (GList CString)
result <- Ptr IconTheme -> IO (Ptr (GList CString))
gtk_icon_theme_list_contexts Ptr IconTheme
iconTheme'
    [CString]
result' <- Ptr (GList CString) -> IO [CString]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList CString)
result
    [Text]
result'' <- (CString -> IO Text) -> [CString] -> IO [Text]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText [CString]
result'
    (CString -> IO ()) -> Ptr (GList CString) -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (GList (Ptr a)) -> IO ()
mapGList CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (GList CString)
result
    Ptr (GList CString) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList CString)
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconTheme
    [Text] -> IO [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result''

#if defined(ENABLE_OVERLOADING)
data IconThemeListContextsMethodInfo
instance (signature ~ (m [T.Text]), MonadIO m, IsIconTheme a) => O.MethodInfo IconThemeListContextsMethodInfo a signature where
    overloadedMethod = iconThemeListContexts

#endif

-- method IconTheme::list_icons
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "icon_theme"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IconTheme" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkIconTheme" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "context"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a string identifying a particular type of\n          icon, or %NULL to list all icons."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TGList (TBasicType TUTF8))
-- throws : False
-- Skip return : False

foreign import ccall "gtk_icon_theme_list_icons" gtk_icon_theme_list_icons :: 
    Ptr IconTheme ->                        -- icon_theme : TInterface (Name {namespace = "Gtk", name = "IconTheme"})
    CString ->                              -- context : TBasicType TUTF8
    IO (Ptr (GList CString))

-- | Lists the icons in the current icon theme. Only a subset
-- of the icons can be listed by providing a context string.
-- The set of values for the context string is system dependent,
-- but will typically include such values as “Applications” and
-- “MimeTypes”. Contexts are explained in the
-- <http://www.freedesktop.org/wiki/Specifications/icon-theme-spec Icon Theme Specification>.
-- The standard contexts are listed in the
-- <http://www.freedesktop.org/wiki/Specifications/icon-naming-spec Icon Naming Specification>.
-- Also see 'GI.Gtk.Objects.IconTheme.iconThemeListContexts'.
-- 
-- /Since: 2.4/
iconThemeListIcons ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
    a
    -- ^ /@iconTheme@/: a t'GI.Gtk.Objects.IconTheme.IconTheme'
    -> Maybe (T.Text)
    -- ^ /@context@/: a string identifying a particular type of
    --           icon, or 'P.Nothing' to list all icons.
    -> m [T.Text]
    -- ^ __Returns:__ a t'GI.GLib.Structs.List.List' list
    --     holding the names of all the icons in the theme. You must
    --     first free each element in the list with 'GI.GLib.Functions.free', then
    --     free the list itself with @/g_list_free()/@.
iconThemeListIcons :: a -> Maybe Text -> m [Text]
iconThemeListIcons iconTheme :: a
iconTheme context :: Maybe Text
context = 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 IconTheme
iconTheme' <- a -> IO (Ptr IconTheme)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iconTheme
    CString
maybeContext <- case Maybe Text
context of
        Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just jContext :: Text
jContext -> do
            CString
jContext' <- Text -> IO CString
textToCString Text
jContext
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jContext'
    Ptr (GList CString)
result <- Ptr IconTheme -> CString -> IO (Ptr (GList CString))
gtk_icon_theme_list_icons Ptr IconTheme
iconTheme' CString
maybeContext
    [CString]
result' <- Ptr (GList CString) -> IO [CString]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList CString)
result
    [Text]
result'' <- (CString -> IO Text) -> [CString] -> IO [Text]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText [CString]
result'
    (CString -> IO ()) -> Ptr (GList CString) -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (GList (Ptr a)) -> IO ()
mapGList CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (GList CString)
result
    Ptr (GList CString) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList CString)
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconTheme
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeContext
    [Text] -> IO [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result''

#if defined(ENABLE_OVERLOADING)
data IconThemeListIconsMethodInfo
instance (signature ~ (Maybe (T.Text) -> m [T.Text]), MonadIO m, IsIconTheme a) => O.MethodInfo IconThemeListIconsMethodInfo a signature where
    overloadedMethod = iconThemeListIcons

#endif

-- method IconTheme::load_icon
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "icon_theme"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IconTheme" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkIconTheme" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "icon_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of the icon to lookup"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the desired icon size. The resulting icon may not be\n    exactly this size; see gtk_icon_info_load_icon()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IconLookupFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "flags modifying the behavior of the icon lookup"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" })
-- throws : True
-- Skip return : False

foreign import ccall "gtk_icon_theme_load_icon" gtk_icon_theme_load_icon :: 
    Ptr IconTheme ->                        -- icon_theme : TInterface (Name {namespace = "Gtk", name = "IconTheme"})
    CString ->                              -- icon_name : TBasicType TUTF8
    Int32 ->                                -- size : TBasicType TInt
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gtk", name = "IconLookupFlags"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr GdkPixbuf.Pixbuf.Pixbuf)

-- | Looks up an icon in an icon theme, scales it to the given size
-- and renders it into a pixbuf. This is a convenience function;
-- if more details about the icon are needed, use
-- 'GI.Gtk.Objects.IconTheme.iconThemeLookupIcon' followed by 'GI.Gtk.Objects.IconInfo.iconInfoLoadIcon'.
-- 
-- Note that you probably want to listen for icon theme changes and
-- update the icon. This is usually done by connecting to the
-- GtkWidget[styleSet](#signal:styleSet) signal. If for some reason you do not want to
-- update the icon when the icon theme changes, you should consider
-- using 'GI.GdkPixbuf.Objects.Pixbuf.pixbufCopy' to make a private copy of the pixbuf
-- returned by this function. Otherwise GTK+ may need to keep the old
-- icon theme loaded, which would be a waste of memory.
-- 
-- /Since: 2.4/
iconThemeLoadIcon ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
    a
    -- ^ /@iconTheme@/: a t'GI.Gtk.Objects.IconTheme.IconTheme'
    -> T.Text
    -- ^ /@iconName@/: the name of the icon to lookup
    -> Int32
    -- ^ /@size@/: the desired icon size. The resulting icon may not be
    --     exactly this size; see 'GI.Gtk.Objects.IconInfo.iconInfoLoadIcon'.
    -> [Gtk.Flags.IconLookupFlags]
    -- ^ /@flags@/: flags modifying the behavior of the icon lookup
    -> m (Maybe GdkPixbuf.Pixbuf.Pixbuf)
    -- ^ __Returns:__ the rendered icon; this may be
    --     a newly created icon or a new reference to an internal icon, so
    --     you must not modify the icon. Use 'GI.GObject.Objects.Object.objectUnref' to release
    --     your reference to the icon. 'P.Nothing' if the icon isn’t found. /(Can throw 'Data.GI.Base.GError.GError')/
iconThemeLoadIcon :: a -> Text -> Int32 -> [IconLookupFlags] -> m (Maybe Pixbuf)
iconThemeLoadIcon iconTheme :: a
iconTheme iconName :: Text
iconName size :: Int32
size flags :: [IconLookupFlags]
flags = 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 IconTheme
iconTheme' <- a -> IO (Ptr IconTheme)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iconTheme
    CString
iconName' <- Text -> IO CString
textToCString Text
iconName
    let flags' :: CUInt
flags' = [IconLookupFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [IconLookupFlags]
flags
    IO (Maybe Pixbuf) -> IO () -> IO (Maybe 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 IconTheme
-> CString -> Int32 -> CUInt -> Ptr (Ptr GError) -> IO (Ptr Pixbuf)
gtk_icon_theme_load_icon Ptr IconTheme
iconTheme' CString
iconName' Int32
size CUInt
flags'
        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
$ \result' :: 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
wrapObject 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
iconTheme
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
iconName'
        Maybe Pixbuf -> IO (Maybe Pixbuf)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Pixbuf
maybeResult
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
iconName'
     )

#if defined(ENABLE_OVERLOADING)
data IconThemeLoadIconMethodInfo
instance (signature ~ (T.Text -> Int32 -> [Gtk.Flags.IconLookupFlags] -> m (Maybe GdkPixbuf.Pixbuf.Pixbuf)), MonadIO m, IsIconTheme a) => O.MethodInfo IconThemeLoadIconMethodInfo a signature where
    overloadedMethod = iconThemeLoadIcon

#endif

-- method IconTheme::load_icon_for_scale
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "icon_theme"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IconTheme" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkIconTheme" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "icon_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of the icon to lookup"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the desired icon size. The resulting icon may not be\n    exactly this size; see gtk_icon_info_load_icon()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "scale"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "desired scale" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IconLookupFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "flags modifying the behavior of the icon lookup"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" })
-- throws : True
-- Skip return : False

foreign import ccall "gtk_icon_theme_load_icon_for_scale" gtk_icon_theme_load_icon_for_scale :: 
    Ptr IconTheme ->                        -- icon_theme : TInterface (Name {namespace = "Gtk", name = "IconTheme"})
    CString ->                              -- icon_name : TBasicType TUTF8
    Int32 ->                                -- size : TBasicType TInt
    Int32 ->                                -- scale : TBasicType TInt
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gtk", name = "IconLookupFlags"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr GdkPixbuf.Pixbuf.Pixbuf)

-- | Looks up an icon in an icon theme for a particular window scale,
-- scales it to the given size and renders it into a pixbuf. This is a
-- convenience function; if more details about the icon are needed,
-- use 'GI.Gtk.Objects.IconTheme.iconThemeLookupIcon' followed by
-- 'GI.Gtk.Objects.IconInfo.iconInfoLoadIcon'.
-- 
-- Note that you probably want to listen for icon theme changes and
-- update the icon. This is usually done by connecting to the
-- GtkWidget[styleSet](#signal:styleSet) signal. If for some reason you do not want to
-- update the icon when the icon theme changes, you should consider
-- using 'GI.GdkPixbuf.Objects.Pixbuf.pixbufCopy' to make a private copy of the pixbuf
-- returned by this function. Otherwise GTK+ may need to keep the old
-- icon theme loaded, which would be a waste of memory.
-- 
-- /Since: 3.10/
iconThemeLoadIconForScale ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
    a
    -- ^ /@iconTheme@/: a t'GI.Gtk.Objects.IconTheme.IconTheme'
    -> T.Text
    -- ^ /@iconName@/: the name of the icon to lookup
    -> Int32
    -- ^ /@size@/: the desired icon size. The resulting icon may not be
    --     exactly this size; see 'GI.Gtk.Objects.IconInfo.iconInfoLoadIcon'.
    -> Int32
    -- ^ /@scale@/: desired scale
    -> [Gtk.Flags.IconLookupFlags]
    -- ^ /@flags@/: flags modifying the behavior of the icon lookup
    -> m (Maybe GdkPixbuf.Pixbuf.Pixbuf)
    -- ^ __Returns:__ the rendered icon; this may be
    --     a newly created icon or a new reference to an internal icon, so
    --     you must not modify the icon. Use 'GI.GObject.Objects.Object.objectUnref' to release
    --     your reference to the icon. 'P.Nothing' if the icon isn’t found. /(Can throw 'Data.GI.Base.GError.GError')/
iconThemeLoadIconForScale :: a
-> Text -> Int32 -> Int32 -> [IconLookupFlags] -> m (Maybe Pixbuf)
iconThemeLoadIconForScale iconTheme :: a
iconTheme iconName :: Text
iconName size :: Int32
size scale :: Int32
scale flags :: [IconLookupFlags]
flags = 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 IconTheme
iconTheme' <- a -> IO (Ptr IconTheme)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iconTheme
    CString
iconName' <- Text -> IO CString
textToCString Text
iconName
    let flags' :: CUInt
flags' = [IconLookupFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [IconLookupFlags]
flags
    IO (Maybe Pixbuf) -> IO () -> IO (Maybe 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 IconTheme
-> CString
-> Int32
-> Int32
-> CUInt
-> Ptr (Ptr GError)
-> IO (Ptr Pixbuf)
gtk_icon_theme_load_icon_for_scale Ptr IconTheme
iconTheme' CString
iconName' Int32
size Int32
scale CUInt
flags'
        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
$ \result' :: 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
wrapObject 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
iconTheme
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
iconName'
        Maybe Pixbuf -> IO (Maybe Pixbuf)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Pixbuf
maybeResult
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
iconName'
     )

#if defined(ENABLE_OVERLOADING)
data IconThemeLoadIconForScaleMethodInfo
instance (signature ~ (T.Text -> Int32 -> Int32 -> [Gtk.Flags.IconLookupFlags] -> m (Maybe GdkPixbuf.Pixbuf.Pixbuf)), MonadIO m, IsIconTheme a) => O.MethodInfo IconThemeLoadIconForScaleMethodInfo a signature where
    overloadedMethod = iconThemeLoadIconForScale

#endif

-- method IconTheme::load_surface
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "icon_theme"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IconTheme" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkIconTheme" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "icon_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of the icon to lookup"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the desired icon size. The resulting icon may not be\n    exactly this size; see gtk_icon_info_load_icon()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "scale"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "desired scale" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "for_window"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Window" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "#GdkWindow to optimize drawing for, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IconLookupFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "flags modifying the behavior of the icon lookup"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "cairo" , name = "Surface" })
-- throws : True
-- Skip return : False

foreign import ccall "gtk_icon_theme_load_surface" gtk_icon_theme_load_surface :: 
    Ptr IconTheme ->                        -- icon_theme : TInterface (Name {namespace = "Gtk", name = "IconTheme"})
    CString ->                              -- icon_name : TBasicType TUTF8
    Int32 ->                                -- size : TBasicType TInt
    Int32 ->                                -- scale : TBasicType TInt
    Ptr Gdk.Window.Window ->                -- for_window : TInterface (Name {namespace = "Gdk", name = "Window"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gtk", name = "IconLookupFlags"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Cairo.Surface.Surface)

-- | Looks up an icon in an icon theme for a particular window scale,
-- scales it to the given size and renders it into a cairo surface. This is a
-- convenience function; if more details about the icon are needed,
-- use 'GI.Gtk.Objects.IconTheme.iconThemeLookupIcon' followed by
-- 'GI.Gtk.Objects.IconInfo.iconInfoLoadSurface'.
-- 
-- Note that you probably want to listen for icon theme changes and
-- update the icon. This is usually done by connecting to the
-- GtkWidget[styleSet](#signal:styleSet) signal.
-- 
-- /Since: 3.10/
iconThemeLoadSurface ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconTheme a, Gdk.Window.IsWindow b) =>
    a
    -- ^ /@iconTheme@/: a t'GI.Gtk.Objects.IconTheme.IconTheme'
    -> T.Text
    -- ^ /@iconName@/: the name of the icon to lookup
    -> Int32
    -- ^ /@size@/: the desired icon size. The resulting icon may not be
    --     exactly this size; see 'GI.Gtk.Objects.IconInfo.iconInfoLoadIcon'.
    -> Int32
    -- ^ /@scale@/: desired scale
    -> Maybe (b)
    -- ^ /@forWindow@/: t'GI.Gdk.Objects.Window.Window' to optimize drawing for, or 'P.Nothing'
    -> [Gtk.Flags.IconLookupFlags]
    -- ^ /@flags@/: flags modifying the behavior of the icon lookup
    -> m (Maybe Cairo.Surface.Surface)
    -- ^ __Returns:__ the rendered icon; this may be
    --     a newly created icon or a new reference to an internal icon, so
    --     you must not modify the icon. Use @/cairo_surface_destroy()/@ to
    --     release your reference to the icon. 'P.Nothing' if the icon isn’t
    --     found. /(Can throw 'Data.GI.Base.GError.GError')/
iconThemeLoadSurface :: a
-> Text
-> Int32
-> Int32
-> Maybe b
-> [IconLookupFlags]
-> m (Maybe Surface)
iconThemeLoadSurface iconTheme :: a
iconTheme iconName :: Text
iconName size :: Int32
size scale :: Int32
scale forWindow :: Maybe b
forWindow flags :: [IconLookupFlags]
flags = IO (Maybe Surface) -> m (Maybe Surface)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Surface) -> m (Maybe Surface))
-> IO (Maybe Surface) -> m (Maybe Surface)
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
    CString
iconName' <- Text -> IO CString
textToCString Text
iconName
    Ptr Window
maybeForWindow <- case Maybe b
forWindow of
        Nothing -> Ptr Window -> IO (Ptr Window)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Window
forall a. Ptr a
nullPtr
        Just jForWindow :: 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'
    let flags' :: CUInt
flags' = [IconLookupFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [IconLookupFlags]
flags
    IO (Maybe Surface) -> IO () -> IO (Maybe 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 IconTheme
-> CString
-> Int32
-> Int32
-> Ptr Window
-> CUInt
-> Ptr (Ptr GError)
-> IO (Ptr Surface)
gtk_icon_theme_load_surface Ptr IconTheme
iconTheme' CString
iconName' Int32
size Int32
scale Ptr Window
maybeForWindow CUInt
flags'
        Maybe Surface
maybeResult <- Ptr Surface -> (Ptr Surface -> IO Surface) -> IO (Maybe Surface)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Surface
result ((Ptr Surface -> IO Surface) -> IO (Maybe Surface))
-> (Ptr Surface -> IO Surface) -> IO (Maybe Surface)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr Surface
result' -> do
            Surface
result'' <- ((ManagedPtr Surface -> Surface) -> Ptr Surface -> IO Surface
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Surface -> Surface
Cairo.Surface.Surface) Ptr Surface
result'
            Surface -> IO Surface
forall (m :: * -> *) a. Monad m => a -> m a
return Surface
result''
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconTheme
        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
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
iconName'
        Maybe Surface -> IO (Maybe Surface)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Surface
maybeResult
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
iconName'
     )

#if defined(ENABLE_OVERLOADING)
data IconThemeLoadSurfaceMethodInfo
instance (signature ~ (T.Text -> Int32 -> Int32 -> Maybe (b) -> [Gtk.Flags.IconLookupFlags] -> m (Maybe Cairo.Surface.Surface)), MonadIO m, IsIconTheme a, Gdk.Window.IsWindow b) => O.MethodInfo IconThemeLoadSurfaceMethodInfo a signature where
    overloadedMethod = iconThemeLoadSurface

#endif

-- method IconTheme::lookup_by_gicon
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "icon_theme"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IconTheme" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkIconTheme" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "icon"
--           , argType = TInterface Name { namespace = "Gio" , name = "Icon" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GIcon to look up"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "desired icon size" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IconLookupFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "flags modifying the behavior of the icon lookup"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "IconInfo" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_icon_theme_lookup_by_gicon" gtk_icon_theme_lookup_by_gicon :: 
    Ptr IconTheme ->                        -- icon_theme : TInterface (Name {namespace = "Gtk", name = "IconTheme"})
    Ptr Gio.Icon.Icon ->                    -- icon : TInterface (Name {namespace = "Gio", name = "Icon"})
    Int32 ->                                -- size : TBasicType TInt
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gtk", name = "IconLookupFlags"})
    IO (Ptr Gtk.IconInfo.IconInfo)

-- | Looks up an icon and returns a t'GI.Gtk.Objects.IconInfo.IconInfo' containing information
-- such as the filename of the icon. The icon can then be rendered
-- into a pixbuf using 'GI.Gtk.Objects.IconInfo.iconInfoLoadIcon'.
-- 
-- When rendering on displays with high pixel densities you should not
-- use a /@size@/ multiplied by the scaling factor returned by functions
-- like 'GI.Gdk.Objects.Window.windowGetScaleFactor'. Instead, you should use
-- 'GI.Gtk.Objects.IconTheme.iconThemeLookupByGiconForScale', as the assets loaded
-- for a given scaling factor may be different.
-- 
-- /Since: 2.14/
iconThemeLookupByGicon ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconTheme a, Gio.Icon.IsIcon b) =>
    a
    -- ^ /@iconTheme@/: a t'GI.Gtk.Objects.IconTheme.IconTheme'
    -> b
    -- ^ /@icon@/: the t'GI.Gio.Interfaces.Icon.Icon' to look up
    -> Int32
    -- ^ /@size@/: desired icon size
    -> [Gtk.Flags.IconLookupFlags]
    -- ^ /@flags@/: flags modifying the behavior of the icon lookup
    -> m (Maybe Gtk.IconInfo.IconInfo)
    -- ^ __Returns:__ a t'GI.Gtk.Objects.IconInfo.IconInfo' containing
    --     information about the icon, or 'P.Nothing' if the icon wasn’t
    --     found. Unref with 'GI.GObject.Objects.Object.objectUnref'
iconThemeLookupByGicon :: a -> b -> Int32 -> [IconLookupFlags] -> m (Maybe IconInfo)
iconThemeLookupByGicon iconTheme :: a
iconTheme icon :: b
icon size :: Int32
size flags :: [IconLookupFlags]
flags = IO (Maybe IconInfo) -> m (Maybe IconInfo)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe IconInfo) -> m (Maybe IconInfo))
-> IO (Maybe IconInfo) -> m (Maybe 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 Icon
icon' <- b -> IO (Ptr Icon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
icon
    let flags' :: CUInt
flags' = [IconLookupFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [IconLookupFlags]
flags
    Ptr IconInfo
result <- Ptr IconTheme -> Ptr Icon -> Int32 -> CUInt -> IO (Ptr IconInfo)
gtk_icon_theme_lookup_by_gicon Ptr IconTheme
iconTheme' Ptr Icon
icon' Int32
size CUInt
flags'
    Maybe IconInfo
maybeResult <- Ptr IconInfo
-> (Ptr IconInfo -> IO IconInfo) -> IO (Maybe IconInfo)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr IconInfo
result ((Ptr IconInfo -> IO IconInfo) -> IO (Maybe IconInfo))
-> (Ptr IconInfo -> IO IconInfo) -> IO (Maybe IconInfo)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr IconInfo
result' -> do
        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
Gtk.IconInfo.IconInfo) Ptr IconInfo
result'
        IconInfo -> IO IconInfo
forall (m :: * -> *) a. Monad m => a -> m a
return IconInfo
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconTheme
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
icon
    Maybe IconInfo -> IO (Maybe IconInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe IconInfo
maybeResult

#if defined(ENABLE_OVERLOADING)
data IconThemeLookupByGiconMethodInfo
instance (signature ~ (b -> Int32 -> [Gtk.Flags.IconLookupFlags] -> m (Maybe Gtk.IconInfo.IconInfo)), MonadIO m, IsIconTheme a, Gio.Icon.IsIcon b) => O.MethodInfo IconThemeLookupByGiconMethodInfo a signature where
    overloadedMethod = iconThemeLookupByGicon

#endif

-- method IconTheme::lookup_by_gicon_for_scale
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "icon_theme"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IconTheme" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkIconTheme" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "icon"
--           , argType = TInterface Name { namespace = "Gio" , name = "Icon" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GIcon to look up"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "desired icon size" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "scale"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the desired scale" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IconLookupFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "flags modifying the behavior of the icon lookup"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "IconInfo" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_icon_theme_lookup_by_gicon_for_scale" gtk_icon_theme_lookup_by_gicon_for_scale :: 
    Ptr IconTheme ->                        -- icon_theme : TInterface (Name {namespace = "Gtk", name = "IconTheme"})
    Ptr Gio.Icon.Icon ->                    -- icon : TInterface (Name {namespace = "Gio", name = "Icon"})
    Int32 ->                                -- size : TBasicType TInt
    Int32 ->                                -- scale : TBasicType TInt
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gtk", name = "IconLookupFlags"})
    IO (Ptr Gtk.IconInfo.IconInfo)

-- | Looks up an icon and returns a t'GI.Gtk.Objects.IconInfo.IconInfo' containing information
-- such as the filename of the icon. The icon can then be rendered into
-- a pixbuf using 'GI.Gtk.Objects.IconInfo.iconInfoLoadIcon'.
-- 
-- /Since: 3.10/
iconThemeLookupByGiconForScale ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconTheme a, Gio.Icon.IsIcon b) =>
    a
    -- ^ /@iconTheme@/: a t'GI.Gtk.Objects.IconTheme.IconTheme'
    -> b
    -- ^ /@icon@/: the t'GI.Gio.Interfaces.Icon.Icon' to look up
    -> Int32
    -- ^ /@size@/: desired icon size
    -> Int32
    -- ^ /@scale@/: the desired scale
    -> [Gtk.Flags.IconLookupFlags]
    -- ^ /@flags@/: flags modifying the behavior of the icon lookup
    -> m (Maybe Gtk.IconInfo.IconInfo)
    -- ^ __Returns:__ a t'GI.Gtk.Objects.IconInfo.IconInfo' containing
    --     information about the icon, or 'P.Nothing' if the icon wasn’t
    --     found. Unref with 'GI.GObject.Objects.Object.objectUnref'
iconThemeLookupByGiconForScale :: a -> b -> Int32 -> Int32 -> [IconLookupFlags] -> m (Maybe IconInfo)
iconThemeLookupByGiconForScale iconTheme :: a
iconTheme icon :: b
icon size :: Int32
size scale :: Int32
scale flags :: [IconLookupFlags]
flags = IO (Maybe IconInfo) -> m (Maybe IconInfo)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe IconInfo) -> m (Maybe IconInfo))
-> IO (Maybe IconInfo) -> m (Maybe 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 Icon
icon' <- b -> IO (Ptr Icon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
icon
    let flags' :: CUInt
flags' = [IconLookupFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [IconLookupFlags]
flags
    Ptr IconInfo
result <- Ptr IconTheme
-> Ptr Icon -> Int32 -> Int32 -> CUInt -> IO (Ptr IconInfo)
gtk_icon_theme_lookup_by_gicon_for_scale Ptr IconTheme
iconTheme' Ptr Icon
icon' Int32
size Int32
scale CUInt
flags'
    Maybe IconInfo
maybeResult <- Ptr IconInfo
-> (Ptr IconInfo -> IO IconInfo) -> IO (Maybe IconInfo)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr IconInfo
result ((Ptr IconInfo -> IO IconInfo) -> IO (Maybe IconInfo))
-> (Ptr IconInfo -> IO IconInfo) -> IO (Maybe IconInfo)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr IconInfo
result' -> do
        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
Gtk.IconInfo.IconInfo) Ptr IconInfo
result'
        IconInfo -> IO IconInfo
forall (m :: * -> *) a. Monad m => a -> m a
return IconInfo
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconTheme
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
icon
    Maybe IconInfo -> IO (Maybe IconInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe IconInfo
maybeResult

#if defined(ENABLE_OVERLOADING)
data IconThemeLookupByGiconForScaleMethodInfo
instance (signature ~ (b -> Int32 -> Int32 -> [Gtk.Flags.IconLookupFlags] -> m (Maybe Gtk.IconInfo.IconInfo)), MonadIO m, IsIconTheme a, Gio.Icon.IsIcon b) => O.MethodInfo IconThemeLookupByGiconForScaleMethodInfo a signature where
    overloadedMethod = iconThemeLookupByGiconForScale

#endif

-- method IconTheme::lookup_icon
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "icon_theme"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IconTheme" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkIconTheme" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "icon_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of the icon to lookup"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "desired icon size" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IconLookupFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "flags modifying the behavior of the icon lookup"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "IconInfo" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_icon_theme_lookup_icon" gtk_icon_theme_lookup_icon :: 
    Ptr IconTheme ->                        -- icon_theme : TInterface (Name {namespace = "Gtk", name = "IconTheme"})
    CString ->                              -- icon_name : TBasicType TUTF8
    Int32 ->                                -- size : TBasicType TInt
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gtk", name = "IconLookupFlags"})
    IO (Ptr Gtk.IconInfo.IconInfo)

-- | Looks up a named icon and returns a t'GI.Gtk.Objects.IconInfo.IconInfo' containing
-- information such as the filename of the icon. The icon
-- can then be rendered into a pixbuf using
-- 'GI.Gtk.Objects.IconInfo.iconInfoLoadIcon'. ('GI.Gtk.Objects.IconTheme.iconThemeLoadIcon'
-- combines these two steps if all you need is the pixbuf.)
-- 
-- When rendering on displays with high pixel densities you should not
-- use a /@size@/ multiplied by the scaling factor returned by functions
-- like 'GI.Gdk.Objects.Window.windowGetScaleFactor'. Instead, you should use
-- 'GI.Gtk.Objects.IconTheme.iconThemeLookupIconForScale', as the assets loaded
-- for a given scaling factor may be different.
-- 
-- /Since: 2.4/
iconThemeLookupIcon ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
    a
    -- ^ /@iconTheme@/: a t'GI.Gtk.Objects.IconTheme.IconTheme'
    -> T.Text
    -- ^ /@iconName@/: the name of the icon to lookup
    -> Int32
    -- ^ /@size@/: desired icon size
    -> [Gtk.Flags.IconLookupFlags]
    -- ^ /@flags@/: flags modifying the behavior of the icon lookup
    -> m (Maybe Gtk.IconInfo.IconInfo)
    -- ^ __Returns:__ a t'GI.Gtk.Objects.IconInfo.IconInfo' object
    --     containing information about the icon, or 'P.Nothing' if the
    --     icon wasn’t found.
iconThemeLookupIcon :: a -> Text -> Int32 -> [IconLookupFlags] -> m (Maybe IconInfo)
iconThemeLookupIcon iconTheme :: a
iconTheme iconName :: Text
iconName size :: Int32
size flags :: [IconLookupFlags]
flags = IO (Maybe IconInfo) -> m (Maybe IconInfo)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe IconInfo) -> m (Maybe IconInfo))
-> IO (Maybe IconInfo) -> m (Maybe 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
    CString
iconName' <- Text -> IO CString
textToCString Text
iconName
    let flags' :: CUInt
flags' = [IconLookupFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [IconLookupFlags]
flags
    Ptr IconInfo
result <- Ptr IconTheme -> CString -> Int32 -> CUInt -> IO (Ptr IconInfo)
gtk_icon_theme_lookup_icon Ptr IconTheme
iconTheme' CString
iconName' Int32
size CUInt
flags'
    Maybe IconInfo
maybeResult <- Ptr IconInfo
-> (Ptr IconInfo -> IO IconInfo) -> IO (Maybe IconInfo)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr IconInfo
result ((Ptr IconInfo -> IO IconInfo) -> IO (Maybe IconInfo))
-> (Ptr IconInfo -> IO IconInfo) -> IO (Maybe IconInfo)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr IconInfo
result' -> do
        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
Gtk.IconInfo.IconInfo) Ptr IconInfo
result'
        IconInfo -> IO IconInfo
forall (m :: * -> *) a. Monad m => a -> m a
return IconInfo
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconTheme
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
iconName'
    Maybe IconInfo -> IO (Maybe IconInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe IconInfo
maybeResult

#if defined(ENABLE_OVERLOADING)
data IconThemeLookupIconMethodInfo
instance (signature ~ (T.Text -> Int32 -> [Gtk.Flags.IconLookupFlags] -> m (Maybe Gtk.IconInfo.IconInfo)), MonadIO m, IsIconTheme a) => O.MethodInfo IconThemeLookupIconMethodInfo a signature where
    overloadedMethod = iconThemeLookupIcon

#endif

-- method IconTheme::lookup_icon_for_scale
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "icon_theme"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IconTheme" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkIconTheme" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "icon_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of the icon to lookup"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "desired icon size" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "scale"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the desired scale" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IconLookupFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "flags modifying the behavior of the icon lookup"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "IconInfo" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_icon_theme_lookup_icon_for_scale" gtk_icon_theme_lookup_icon_for_scale :: 
    Ptr IconTheme ->                        -- icon_theme : TInterface (Name {namespace = "Gtk", name = "IconTheme"})
    CString ->                              -- icon_name : TBasicType TUTF8
    Int32 ->                                -- size : TBasicType TInt
    Int32 ->                                -- scale : TBasicType TInt
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gtk", name = "IconLookupFlags"})
    IO (Ptr Gtk.IconInfo.IconInfo)

-- | Looks up a named icon for a particular window scale and returns a
-- t'GI.Gtk.Objects.IconInfo.IconInfo' containing information such as the filename of the
-- icon. The icon can then be rendered into a pixbuf using
-- 'GI.Gtk.Objects.IconInfo.iconInfoLoadIcon'. ('GI.Gtk.Objects.IconTheme.iconThemeLoadIcon' combines
-- these two steps if all you need is the pixbuf.)
-- 
-- /Since: 3.10/
iconThemeLookupIconForScale ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
    a
    -- ^ /@iconTheme@/: a t'GI.Gtk.Objects.IconTheme.IconTheme'
    -> T.Text
    -- ^ /@iconName@/: the name of the icon to lookup
    -> Int32
    -- ^ /@size@/: desired icon size
    -> Int32
    -- ^ /@scale@/: the desired scale
    -> [Gtk.Flags.IconLookupFlags]
    -- ^ /@flags@/: flags modifying the behavior of the icon lookup
    -> m (Maybe Gtk.IconInfo.IconInfo)
    -- ^ __Returns:__ a t'GI.Gtk.Objects.IconInfo.IconInfo' object
    --     containing information about the icon, or 'P.Nothing' if the
    --     icon wasn’t found.
iconThemeLookupIconForScale :: a
-> Text
-> Int32
-> Int32
-> [IconLookupFlags]
-> m (Maybe IconInfo)
iconThemeLookupIconForScale iconTheme :: a
iconTheme iconName :: Text
iconName size :: Int32
size scale :: Int32
scale flags :: [IconLookupFlags]
flags = IO (Maybe IconInfo) -> m (Maybe IconInfo)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe IconInfo) -> m (Maybe IconInfo))
-> IO (Maybe IconInfo) -> m (Maybe 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
    CString
iconName' <- Text -> IO CString
textToCString Text
iconName
    let flags' :: CUInt
flags' = [IconLookupFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [IconLookupFlags]
flags
    Ptr IconInfo
result <- Ptr IconTheme
-> CString -> Int32 -> Int32 -> CUInt -> IO (Ptr IconInfo)
gtk_icon_theme_lookup_icon_for_scale Ptr IconTheme
iconTheme' CString
iconName' Int32
size Int32
scale CUInt
flags'
    Maybe IconInfo
maybeResult <- Ptr IconInfo
-> (Ptr IconInfo -> IO IconInfo) -> IO (Maybe IconInfo)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr IconInfo
result ((Ptr IconInfo -> IO IconInfo) -> IO (Maybe IconInfo))
-> (Ptr IconInfo -> IO IconInfo) -> IO (Maybe IconInfo)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr IconInfo
result' -> do
        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
Gtk.IconInfo.IconInfo) Ptr IconInfo
result'
        IconInfo -> IO IconInfo
forall (m :: * -> *) a. Monad m => a -> m a
return IconInfo
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconTheme
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
iconName'
    Maybe IconInfo -> IO (Maybe IconInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe IconInfo
maybeResult

#if defined(ENABLE_OVERLOADING)
data IconThemeLookupIconForScaleMethodInfo
instance (signature ~ (T.Text -> Int32 -> Int32 -> [Gtk.Flags.IconLookupFlags] -> m (Maybe Gtk.IconInfo.IconInfo)), MonadIO m, IsIconTheme a) => O.MethodInfo IconThemeLookupIconForScaleMethodInfo a signature where
    overloadedMethod = iconThemeLookupIconForScale

#endif

-- method IconTheme::prepend_search_path
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "icon_theme"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IconTheme" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkIconTheme" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "path"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "directory name to prepend to the icon path"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_icon_theme_prepend_search_path" gtk_icon_theme_prepend_search_path :: 
    Ptr IconTheme ->                        -- icon_theme : TInterface (Name {namespace = "Gtk", name = "IconTheme"})
    CString ->                              -- path : TBasicType TFileName
    IO ()

-- | Prepends a directory to the search path.
-- See 'GI.Gtk.Objects.IconTheme.iconThemeSetSearchPath'.
-- 
-- /Since: 2.4/
iconThemePrependSearchPath ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
    a
    -- ^ /@iconTheme@/: a t'GI.Gtk.Objects.IconTheme.IconTheme'
    -> [Char]
    -- ^ /@path@/: directory name to prepend to the icon path
    -> m ()
iconThemePrependSearchPath :: a -> [Char] -> m ()
iconThemePrependSearchPath iconTheme :: a
iconTheme path :: [Char]
path = 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 IconTheme
iconTheme' <- a -> IO (Ptr IconTheme)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iconTheme
    CString
path' <- [Char] -> IO CString
stringToCString [Char]
path
    Ptr IconTheme -> CString -> IO ()
gtk_icon_theme_prepend_search_path Ptr IconTheme
iconTheme' CString
path'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconTheme
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data IconThemePrependSearchPathMethodInfo
instance (signature ~ ([Char] -> m ()), MonadIO m, IsIconTheme a) => O.MethodInfo IconThemePrependSearchPathMethodInfo a signature where
    overloadedMethod = iconThemePrependSearchPath

#endif

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

foreign import ccall "gtk_icon_theme_rescan_if_needed" gtk_icon_theme_rescan_if_needed :: 
    Ptr IconTheme ->                        -- icon_theme : TInterface (Name {namespace = "Gtk", name = "IconTheme"})
    IO CInt

-- | Checks to see if the icon theme has changed; if it has, any
-- currently cached information is discarded and will be reloaded
-- next time /@iconTheme@/ is accessed.
-- 
-- /Since: 2.4/
iconThemeRescanIfNeeded ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
    a
    -- ^ /@iconTheme@/: a t'GI.Gtk.Objects.IconTheme.IconTheme'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the icon theme has changed and needed
    --     to be reloaded.
iconThemeRescanIfNeeded :: a -> m Bool
iconThemeRescanIfNeeded iconTheme :: a
iconTheme = 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 IconTheme
iconTheme' <- a -> IO (Ptr IconTheme)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iconTheme
    CInt
result <- Ptr IconTheme -> IO CInt
gtk_icon_theme_rescan_if_needed Ptr IconTheme
iconTheme'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconTheme
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data IconThemeRescanIfNeededMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsIconTheme a) => O.MethodInfo IconThemeRescanIfNeededMethodInfo a signature where
    overloadedMethod = iconThemeRescanIfNeeded

#endif

-- method IconTheme::set_custom_theme
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "icon_theme"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IconTheme" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkIconTheme" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "theme_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "name of icon theme to use instead of\n  configured theme, or %NULL to unset a previously set custom theme"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_icon_theme_set_custom_theme" gtk_icon_theme_set_custom_theme :: 
    Ptr IconTheme ->                        -- icon_theme : TInterface (Name {namespace = "Gtk", name = "IconTheme"})
    CString ->                              -- theme_name : TBasicType TUTF8
    IO ()

-- | Sets the name of the icon theme that the t'GI.Gtk.Objects.IconTheme.IconTheme' object uses
-- overriding system configuration. This function cannot be called
-- on the icon theme objects returned from 'GI.Gtk.Objects.IconTheme.iconThemeGetDefault'
-- and 'GI.Gtk.Objects.IconTheme.iconThemeGetForScreen'.
-- 
-- /Since: 2.4/
iconThemeSetCustomTheme ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
    a
    -- ^ /@iconTheme@/: a t'GI.Gtk.Objects.IconTheme.IconTheme'
    -> Maybe (T.Text)
    -- ^ /@themeName@/: name of icon theme to use instead of
    --   configured theme, or 'P.Nothing' to unset a previously set custom theme
    -> m ()
iconThemeSetCustomTheme :: a -> Maybe Text -> m ()
iconThemeSetCustomTheme iconTheme :: a
iconTheme themeName :: Maybe Text
themeName = 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 IconTheme
iconTheme' <- a -> IO (Ptr IconTheme)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iconTheme
    CString
maybeThemeName <- case Maybe Text
themeName of
        Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just jThemeName :: Text
jThemeName -> do
            CString
jThemeName' <- Text -> IO CString
textToCString Text
jThemeName
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jThemeName'
    Ptr IconTheme -> CString -> IO ()
gtk_icon_theme_set_custom_theme Ptr IconTheme
iconTheme' CString
maybeThemeName
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconTheme
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeThemeName
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data IconThemeSetCustomThemeMethodInfo
instance (signature ~ (Maybe (T.Text) -> m ()), MonadIO m, IsIconTheme a) => O.MethodInfo IconThemeSetCustomThemeMethodInfo a signature where
    overloadedMethod = iconThemeSetCustomTheme

#endif

-- method IconTheme::set_screen
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "icon_theme"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IconTheme" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkIconTheme" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "screen"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Screen" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkScreen" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_icon_theme_set_screen" gtk_icon_theme_set_screen :: 
    Ptr IconTheme ->                        -- icon_theme : TInterface (Name {namespace = "Gtk", name = "IconTheme"})
    Ptr Gdk.Screen.Screen ->                -- screen : TInterface (Name {namespace = "Gdk", name = "Screen"})
    IO ()

-- | Sets the screen for an icon theme; the screen is used
-- to track the user’s currently configured icon theme,
-- which might be different for different screens.
-- 
-- /Since: 2.4/
iconThemeSetScreen ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconTheme a, Gdk.Screen.IsScreen b) =>
    a
    -- ^ /@iconTheme@/: a t'GI.Gtk.Objects.IconTheme.IconTheme'
    -> b
    -- ^ /@screen@/: a t'GI.Gdk.Objects.Screen.Screen'
    -> m ()
iconThemeSetScreen :: a -> b -> m ()
iconThemeSetScreen iconTheme :: a
iconTheme screen :: b
screen = 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 IconTheme
iconTheme' <- a -> IO (Ptr IconTheme)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iconTheme
    Ptr Screen
screen' <- b -> IO (Ptr Screen)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
screen
    Ptr IconTheme -> Ptr Screen -> IO ()
gtk_icon_theme_set_screen Ptr IconTheme
iconTheme' Ptr Screen
screen'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconTheme
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
screen
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data IconThemeSetScreenMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsIconTheme a, Gdk.Screen.IsScreen b) => O.MethodInfo IconThemeSetScreenMethodInfo a signature where
    overloadedMethod = iconThemeSetScreen

#endif

-- method IconTheme::set_search_path
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "icon_theme"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IconTheme" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkIconTheme" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "path"
--           , argType = TCArray False (-1) 2 (TBasicType TFileName)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "array of\n    directories that are searched for icon themes"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_elements"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of elements in @path."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "n_elements"
--              , argType = TBasicType TInt
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "number of elements in @path."
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_icon_theme_set_search_path" gtk_icon_theme_set_search_path :: 
    Ptr IconTheme ->                        -- icon_theme : TInterface (Name {namespace = "Gtk", name = "IconTheme"})
    Ptr CString ->                          -- path : TCArray False (-1) 2 (TBasicType TFileName)
    Int32 ->                                -- n_elements : TBasicType TInt
    IO ()

-- | Sets the search path for the icon theme object. When looking
-- for an icon theme, GTK+ will search for a subdirectory of
-- one or more of the directories in /@path@/ with the same name
-- as the icon theme containing an index.theme file. (Themes from
-- multiple of the path elements are combined to allow themes to be
-- extended by adding icons in the user’s home directory.)
-- 
-- In addition if an icon found isn’t found either in the current
-- icon theme or the default icon theme, and an image file with
-- the right name is found directly in one of the elements of
-- /@path@/, then that image will be used for the icon name.
-- (This is legacy feature, and new icons should be put
-- into the fallback icon theme, which is called hicolor,
-- rather than directly on the icon path.)
-- 
-- /Since: 2.4/
iconThemeSetSearchPath ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
    a
    -- ^ /@iconTheme@/: a t'GI.Gtk.Objects.IconTheme.IconTheme'
    -> [[Char]]
    -- ^ /@path@/: array of
    --     directories that are searched for icon themes
    -> m ()
iconThemeSetSearchPath :: a -> [[Char]] -> m ()
iconThemeSetSearchPath iconTheme :: a
iconTheme path :: [[Char]]
path = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    let nElements :: Int32
nElements = Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> Int -> Int32
forall a b. (a -> b) -> a -> b
$ [[Char]] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [[Char]]
path
    Ptr IconTheme
iconTheme' <- a -> IO (Ptr IconTheme)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
iconTheme
    Ptr CString
path' <- [[Char]] -> IO (Ptr CString)
packFileNameArray [[Char]]
path
    Ptr IconTheme -> Ptr CString -> Int32 -> IO ()
gtk_icon_theme_set_search_path Ptr IconTheme
iconTheme' Ptr CString
path' Int32
nElements
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
iconTheme
    (Int32 -> (CString -> IO ()) -> Ptr CString -> IO ()
forall a b c.
(Storable a, Integral b) =>
b -> (a -> IO c) -> Ptr a -> IO ()
mapCArrayWithLength Int32
nElements) CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
path'
    Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
path'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data IconThemeSetSearchPathMethodInfo
instance (signature ~ ([[Char]] -> m ()), MonadIO m, IsIconTheme a) => O.MethodInfo IconThemeSetSearchPathMethodInfo a signature where
    overloadedMethod = iconThemeSetSearchPath

#endif

-- method IconTheme::add_builtin_icon
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "icon_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of the icon to register"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the size in pixels at which to register the icon (different\n    images can be registered for the same icon name at different sizes.)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pixbuf"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "#GdkPixbuf that contains the image to use for @icon_name"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_icon_theme_add_builtin_icon" gtk_icon_theme_add_builtin_icon :: 
    CString ->                              -- icon_name : TBasicType TUTF8
    Int32 ->                                -- size : TBasicType TInt
    Ptr GdkPixbuf.Pixbuf.Pixbuf ->          -- pixbuf : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    IO ()

{-# DEPRECATED iconThemeAddBuiltinIcon ["(Since version 3.14)","Use 'GI.Gtk.Objects.IconTheme.iconThemeAddResourcePath'","    to add application-specific icons to the icon theme."] #-}
-- | Registers a built-in icon for icon theme lookups. The idea
-- of built-in icons is to allow an application or library
-- that uses themed icons to function requiring files to
-- be present in the file system. For instance, the default
-- images for all of GTK+’s stock icons are registered
-- as built-icons.
-- 
-- In general, if you use 'GI.Gtk.Objects.IconTheme.iconThemeAddBuiltinIcon'
-- you should also install the icon in the icon theme, so
-- that the icon is generally available.
-- 
-- This function will generally be used with pixbufs loaded
-- via 'GI.GdkPixbuf.Objects.Pixbuf.pixbufNewFromInline'.
-- 
-- /Since: 2.4/
iconThemeAddBuiltinIcon ::
    (B.CallStack.HasCallStack, MonadIO m, GdkPixbuf.Pixbuf.IsPixbuf a) =>
    T.Text
    -- ^ /@iconName@/: the name of the icon to register
    -> Int32
    -- ^ /@size@/: the size in pixels at which to register the icon (different
    --     images can be registered for the same icon name at different sizes.)
    -> a
    -- ^ /@pixbuf@/: t'GI.GdkPixbuf.Objects.Pixbuf.Pixbuf' that contains the image to use for /@iconName@/
    -> m ()
iconThemeAddBuiltinIcon :: Text -> Int32 -> a -> m ()
iconThemeAddBuiltinIcon iconName :: Text
iconName size :: Int32
size pixbuf :: a
pixbuf = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    CString
iconName' <- Text -> IO CString
textToCString Text
iconName
    Ptr Pixbuf
pixbuf' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pixbuf
    CString -> Int32 -> Ptr Pixbuf -> IO ()
gtk_icon_theme_add_builtin_icon CString
iconName' Int32
size Ptr Pixbuf
pixbuf'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pixbuf
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
iconName'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

-- method IconTheme::get_default
-- method type : MemberFunction
-- Args: []
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "IconTheme" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_icon_theme_get_default" gtk_icon_theme_get_default :: 
    IO (Ptr IconTheme)

-- | Gets the icon theme for the default screen. See
-- 'GI.Gtk.Objects.IconTheme.iconThemeGetForScreen'.
-- 
-- /Since: 2.4/
iconThemeGetDefault ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m IconTheme
    -- ^ __Returns:__ A unique t'GI.Gtk.Objects.IconTheme.IconTheme' associated with
    --     the default screen. This icon theme is associated with
    --     the screen and can be used as long as the screen
    --     is open. Do not ref or unref it.
iconThemeGetDefault :: m IconTheme
iconThemeGetDefault  = IO IconTheme -> m IconTheme
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO IconTheme -> m IconTheme) -> IO IconTheme -> m IconTheme
forall a b. (a -> b) -> a -> b
$ do
    Ptr IconTheme
result <- IO (Ptr IconTheme)
gtk_icon_theme_get_default
    Text -> Ptr IconTheme -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "iconThemeGetDefault" Ptr IconTheme
result
    IconTheme
result' <- ((ManagedPtr IconTheme -> IconTheme)
-> Ptr IconTheme -> IO IconTheme
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr IconTheme -> IconTheme
IconTheme) Ptr IconTheme
result
    IconTheme -> IO IconTheme
forall (m :: * -> *) a. Monad m => a -> m a
return IconTheme
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method IconTheme::get_for_screen
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "screen"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Screen" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkScreen" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "IconTheme" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_icon_theme_get_for_screen" gtk_icon_theme_get_for_screen :: 
    Ptr Gdk.Screen.Screen ->                -- screen : TInterface (Name {namespace = "Gdk", name = "Screen"})
    IO (Ptr IconTheme)

-- | Gets the icon theme object associated with /@screen@/; if this
-- function has not previously been called for the given
-- screen, a new icon theme object will be created and
-- associated with the screen. Icon theme objects are
-- fairly expensive to create, so using this function
-- is usually a better choice than calling than 'GI.Gtk.Objects.IconTheme.iconThemeNew'
-- and setting the screen yourself; by using this function
-- a single icon theme object will be shared between users.
-- 
-- /Since: 2.4/
iconThemeGetForScreen ::
    (B.CallStack.HasCallStack, MonadIO m, Gdk.Screen.IsScreen a) =>
    a
    -- ^ /@screen@/: a t'GI.Gdk.Objects.Screen.Screen'
    -> m IconTheme
    -- ^ __Returns:__ A unique t'GI.Gtk.Objects.IconTheme.IconTheme' associated with
    --  the given screen. This icon theme is associated with
    --  the screen and can be used as long as the screen
    --  is open. Do not ref or unref it.
iconThemeGetForScreen :: a -> m IconTheme
iconThemeGetForScreen screen :: a
screen = IO IconTheme -> m IconTheme
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO IconTheme -> m IconTheme) -> IO IconTheme -> m IconTheme
forall a b. (a -> b) -> a -> b
$ do
    Ptr Screen
screen' <- a -> IO (Ptr Screen)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
screen
    Ptr IconTheme
result <- Ptr Screen -> IO (Ptr IconTheme)
gtk_icon_theme_get_for_screen Ptr Screen
screen'
    Text -> Ptr IconTheme -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "iconThemeGetForScreen" Ptr IconTheme
result
    IconTheme
result' <- ((ManagedPtr IconTheme -> IconTheme)
-> Ptr IconTheme -> IO IconTheme
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr IconTheme -> IconTheme
IconTheme) Ptr IconTheme
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
screen
    IconTheme -> IO IconTheme
forall (m :: * -> *) a. Monad m => a -> m a
return IconTheme
result'

#if defined(ENABLE_OVERLOADING)
#endif