{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Objects.IconTheme
    ( 
    IconTheme(..)                           ,
    IsIconTheme                             ,
    toIconTheme                             ,
 
#if defined(ENABLE_OVERLOADING)
    ResolveIconThemeMethod                  ,
#endif
#if defined(ENABLE_OVERLOADING)
    IconThemeAddResourcePathMethodInfo      ,
#endif
    iconThemeAddResourcePath                ,
#if defined(ENABLE_OVERLOADING)
    IconThemeAddSearchPathMethodInfo        ,
#endif
    iconThemeAddSearchPath                  ,
#if defined(ENABLE_OVERLOADING)
    IconThemeGetDisplayMethodInfo           ,
#endif
    iconThemeGetDisplay                     ,
    iconThemeGetForDisplay                  ,
#if defined(ENABLE_OVERLOADING)
    IconThemeGetIconNamesMethodInfo         ,
#endif
    iconThemeGetIconNames                   ,
#if defined(ENABLE_OVERLOADING)
    IconThemeGetIconSizesMethodInfo         ,
#endif
    iconThemeGetIconSizes                   ,
#if defined(ENABLE_OVERLOADING)
    IconThemeGetResourcePathMethodInfo      ,
#endif
    iconThemeGetResourcePath                ,
#if defined(ENABLE_OVERLOADING)
    IconThemeGetSearchPathMethodInfo        ,
#endif
    iconThemeGetSearchPath                  ,
#if defined(ENABLE_OVERLOADING)
    IconThemeGetThemeNameMethodInfo         ,
#endif
    iconThemeGetThemeName                   ,
#if defined(ENABLE_OVERLOADING)
    IconThemeHasGiconMethodInfo             ,
#endif
    iconThemeHasGicon                       ,
#if defined(ENABLE_OVERLOADING)
    IconThemeHasIconMethodInfo              ,
#endif
    iconThemeHasIcon                        ,
#if defined(ENABLE_OVERLOADING)
    IconThemeLookupByGiconMethodInfo        ,
#endif
    iconThemeLookupByGicon                  ,
#if defined(ENABLE_OVERLOADING)
    IconThemeLookupIconMethodInfo           ,
#endif
    iconThemeLookupIcon                     ,
    iconThemeNew                            ,
#if defined(ENABLE_OVERLOADING)
    IconThemeSetResourcePathMethodInfo      ,
#endif
    iconThemeSetResourcePath                ,
#if defined(ENABLE_OVERLOADING)
    IconThemeSetSearchPathMethodInfo        ,
#endif
    iconThemeSetSearchPath                  ,
#if defined(ENABLE_OVERLOADING)
    IconThemeSetThemeNameMethodInfo         ,
#endif
    iconThemeSetThemeName                   ,
 
#if defined(ENABLE_OVERLOADING)
    IconThemeDisplayPropertyInfo            ,
#endif
    clearIconThemeDisplay                   ,
    constructIconThemeDisplay               ,
    getIconThemeDisplay                     ,
#if defined(ENABLE_OVERLOADING)
    iconThemeDisplay                        ,
#endif
    setIconThemeDisplay                     ,
#if defined(ENABLE_OVERLOADING)
    IconThemeIconNamesPropertyInfo          ,
#endif
    getIconThemeIconNames                   ,
#if defined(ENABLE_OVERLOADING)
    iconThemeIconNames                      ,
#endif
#if defined(ENABLE_OVERLOADING)
    IconThemeResourcePathPropertyInfo       ,
#endif
    clearIconThemeResourcePath              ,
    constructIconThemeResourcePath          ,
    getIconThemeResourcePath                ,
#if defined(ENABLE_OVERLOADING)
    iconThemeResourcePath                   ,
#endif
    setIconThemeResourcePath                ,
#if defined(ENABLE_OVERLOADING)
    IconThemeSearchPathPropertyInfo         ,
#endif
    clearIconThemeSearchPath                ,
    constructIconThemeSearchPath            ,
    getIconThemeSearchPath                  ,
#if defined(ENABLE_OVERLOADING)
    iconThemeSearchPath                     ,
#endif
    setIconThemeSearchPath                  ,
#if defined(ENABLE_OVERLOADING)
    IconThemeThemeNamePropertyInfo          ,
#endif
    clearIconThemeThemeName                 ,
    constructIconThemeThemeName             ,
    getIconThemeThemeName                   ,
#if defined(ENABLE_OVERLOADING)
    iconThemeThemeName                      ,
#endif
    setIconThemeThemeName                   ,
 
    IconThemeChangedCallback                ,
#if defined(ENABLE_OVERLOADING)
    IconThemeChangedSignalInfo              ,
#endif
    afterIconThemeChanged                   ,
    onIconThemeChanged                      ,
    ) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Objects.Display as Gdk.Display
import qualified GI.Gio.Interfaces.Icon as Gio.Icon
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Flags as Gtk.Flags
import {-# SOURCE #-} qualified GI.Gtk.Objects.IconPaintable as Gtk.IconPaintable
newtype IconTheme = IconTheme (SP.ManagedPtr IconTheme)
    deriving (IconTheme -> IconTheme -> Bool
(IconTheme -> IconTheme -> Bool)
-> (IconTheme -> IconTheme -> Bool) -> Eq IconTheme
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IconTheme -> IconTheme -> Bool
== :: IconTheme -> IconTheme -> Bool
$c/= :: IconTheme -> IconTheme -> Bool
/= :: IconTheme -> IconTheme -> Bool
Eq)
instance SP.ManagedPtrNewtype IconTheme where
    toManagedPtr :: IconTheme -> ManagedPtr IconTheme
toManagedPtr (IconTheme ManagedPtr IconTheme
p) = ManagedPtr IconTheme
p
foreign import ccall "gtk_icon_theme_get_type"
    c_gtk_icon_theme_get_type :: IO B.Types.GType
instance B.Types.TypedObject IconTheme where
    glibType :: IO GType
glibType = IO GType
c_gtk_icon_theme_get_type
instance B.Types.GObject IconTheme
class (SP.GObject o, O.IsDescendantOf IconTheme o) => IsIconTheme o
instance (SP.GObject o, O.IsDescendantOf IconTheme o) => IsIconTheme o
instance O.HasParentTypes IconTheme
type instance O.ParentTypes IconTheme = '[GObject.Object.Object]
toIconTheme :: (MIO.MonadIO m, IsIconTheme o) => o -> m IconTheme
toIconTheme :: forall (m :: * -> *) o.
(MonadIO m, IsIconTheme o) =>
o -> m IconTheme
toIconTheme = IO IconTheme -> m IconTheme
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr IconTheme -> IconTheme
IconTheme
instance B.GValue.IsGValue (Maybe IconTheme) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_icon_theme_get_type
    gvalueSet_ :: Ptr GValue -> Maybe IconTheme -> IO ()
gvalueSet_ Ptr GValue
gv Maybe IconTheme
P.Nothing = Ptr GValue -> Ptr IconTheme -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr IconTheme
forall a. Ptr a
FP.nullPtr :: FP.Ptr IconTheme)
    gvalueSet_ Ptr GValue
gv (P.Just IconTheme
obj) = IconTheme -> (Ptr IconTheme -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr IconTheme
obj (Ptr GValue -> Ptr IconTheme -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe IconTheme)
gvalueGet_ Ptr GValue
gv = do
        Ptr IconTheme
ptr <- Ptr GValue -> IO (Ptr IconTheme)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr IconTheme)
        if Ptr IconTheme
ptr Ptr IconTheme -> Ptr IconTheme -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr IconTheme
forall a. Ptr a
FP.nullPtr
        then IconTheme -> Maybe IconTheme
forall a. a -> Maybe a
P.Just (IconTheme -> Maybe IconTheme)
-> IO IconTheme -> IO (Maybe IconTheme)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (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
        else Maybe IconTheme -> IO (Maybe IconTheme)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe IconTheme
forall a. Maybe a
P.Nothing
        
    
#if defined(ENABLE_OVERLOADING)
type family ResolveIconThemeMethod (t :: Symbol) (o :: *) :: * where
    ResolveIconThemeMethod "addResourcePath" o = IconThemeAddResourcePathMethodInfo
    ResolveIconThemeMethod "addSearchPath" o = IconThemeAddSearchPathMethodInfo
    ResolveIconThemeMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveIconThemeMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveIconThemeMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveIconThemeMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveIconThemeMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveIconThemeMethod "hasGicon" o = IconThemeHasGiconMethodInfo
    ResolveIconThemeMethod "hasIcon" o = IconThemeHasIconMethodInfo
    ResolveIconThemeMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveIconThemeMethod "lookupByGicon" o = IconThemeLookupByGiconMethodInfo
    ResolveIconThemeMethod "lookupIcon" o = IconThemeLookupIconMethodInfo
    ResolveIconThemeMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveIconThemeMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveIconThemeMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveIconThemeMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    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 "getDisplay" o = IconThemeGetDisplayMethodInfo
    ResolveIconThemeMethod "getIconNames" o = IconThemeGetIconNamesMethodInfo
    ResolveIconThemeMethod "getIconSizes" o = IconThemeGetIconSizesMethodInfo
    ResolveIconThemeMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveIconThemeMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveIconThemeMethod "getResourcePath" o = IconThemeGetResourcePathMethodInfo
    ResolveIconThemeMethod "getSearchPath" o = IconThemeGetSearchPathMethodInfo
    ResolveIconThemeMethod "getThemeName" o = IconThemeGetThemeNameMethodInfo
    ResolveIconThemeMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveIconThemeMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveIconThemeMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveIconThemeMethod "setResourcePath" o = IconThemeSetResourcePathMethodInfo
    ResolveIconThemeMethod "setSearchPath" o = IconThemeSetSearchPathMethodInfo
    ResolveIconThemeMethod "setThemeName" o = IconThemeSetThemeNameMethodInfo
    ResolveIconThemeMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveIconThemeMethod t IconTheme, O.OverloadedMethod 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
#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveIconThemeMethod t IconTheme, O.OverloadedMethod info IconTheme p, R.HasField t IconTheme p) => R.HasField t IconTheme p where
    getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveIconThemeMethod t IconTheme, O.OverloadedMethodInfo info IconTheme) => OL.IsLabel t (O.MethodProxy info IconTheme) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif
#endif
type IconThemeChangedCallback =
    IO ()
type C_IconThemeChangedCallback =
    Ptr IconTheme ->                        
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_IconThemeChangedCallback :: C_IconThemeChangedCallback -> IO (FunPtr C_IconThemeChangedCallback)
wrap_IconThemeChangedCallback :: 
    GObject a => (a -> IconThemeChangedCallback) ->
    C_IconThemeChangedCallback
wrap_IconThemeChangedCallback :: forall a. GObject a => (a -> IO ()) -> C_IconThemeChangedCallback
wrap_IconThemeChangedCallback a -> IO ()
gi'cb Ptr IconTheme
gi'selfPtr Ptr ()
_ = do
    Ptr IconTheme -> (IconTheme -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr IconTheme
gi'selfPtr ((IconTheme -> IO ()) -> IO ()) -> (IconTheme -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \IconTheme
gi'self -> a -> IO ()
gi'cb (IconTheme -> a
forall a b. Coercible a b => a -> b
Coerce.coerce IconTheme
gi'self) 
onIconThemeChanged :: (IsIconTheme a, MonadIO m) => a -> ((?self :: a) => IconThemeChangedCallback) -> m SignalHandlerId
onIconThemeChanged :: forall a (m :: * -> *).
(IsIconTheme a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onIconThemeChanged a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
    let wrapped' :: C_IconThemeChangedCallback
wrapped' = (a -> IO ()) -> C_IconThemeChangedCallback
forall a. GObject a => (a -> IO ()) -> C_IconThemeChangedCallback
wrap_IconThemeChangedCallback a -> IO ()
wrapped
    FunPtr C_IconThemeChangedCallback
wrapped'' <- C_IconThemeChangedCallback
-> IO (FunPtr C_IconThemeChangedCallback)
mk_IconThemeChangedCallback C_IconThemeChangedCallback
wrapped'
    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 Text
"changed" FunPtr C_IconThemeChangedCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterIconThemeChanged :: (IsIconTheme a, MonadIO m) => a -> ((?self :: a) => IconThemeChangedCallback) -> m SignalHandlerId
afterIconThemeChanged :: forall a (m :: * -> *).
(IsIconTheme a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterIconThemeChanged a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
    let wrapped' :: C_IconThemeChangedCallback
wrapped' = (a -> IO ()) -> C_IconThemeChangedCallback
forall a. GObject a => (a -> IO ()) -> C_IconThemeChangedCallback
wrap_IconThemeChangedCallback a -> IO ()
wrapped
    FunPtr C_IconThemeChangedCallback
wrapped'' <- C_IconThemeChangedCallback
-> IO (FunPtr C_IconThemeChangedCallback)
mk_IconThemeChangedCallback C_IconThemeChangedCallback
wrapped'
    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 Text
"changed" FunPtr C_IconThemeChangedCallback
wrapped'' 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
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.IconTheme::changed"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-IconTheme.html#g:signal:changed"})
#endif
   
   
   
getIconThemeDisplay :: (MonadIO m, IsIconTheme o) => o -> m (Maybe Gdk.Display.Display)
getIconThemeDisplay :: forall (m :: * -> *) o.
(MonadIO m, IsIconTheme o) =>
o -> m (Maybe Display)
getIconThemeDisplay o
obj = IO (Maybe Display) -> m (Maybe Display)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Display) -> m (Maybe Display))
-> IO (Maybe Display) -> m (Maybe Display)
forall a b. (a -> b) -> a -> b
$ o
-> String -> (ManagedPtr Display -> Display) -> IO (Maybe Display)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"display" ManagedPtr Display -> Display
Gdk.Display.Display
setIconThemeDisplay :: (MonadIO m, IsIconTheme o, Gdk.Display.IsDisplay a) => o -> a -> m ()
setIconThemeDisplay :: forall (m :: * -> *) o a.
(MonadIO m, IsIconTheme o, IsDisplay a) =>
o -> a -> m ()
setIconThemeDisplay o
obj a
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"display" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructIconThemeDisplay :: (IsIconTheme o, MIO.MonadIO m, Gdk.Display.IsDisplay a) => a -> m (GValueConstruct o)
constructIconThemeDisplay :: forall o (m :: * -> *) a.
(IsIconTheme o, MonadIO m, IsDisplay a) =>
a -> m (GValueConstruct o)
constructIconThemeDisplay a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"display" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
clearIconThemeDisplay :: (MonadIO m, IsIconTheme o) => o -> m ()
clearIconThemeDisplay :: forall (m :: * -> *) o. (MonadIO m, IsIconTheme o) => o -> m ()
clearIconThemeDisplay o
obj = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Display -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"display" (Maybe Display
forall a. Maybe a
Nothing :: Maybe Gdk.Display.Display)
#if defined(ENABLE_OVERLOADING)
data IconThemeDisplayPropertyInfo
instance AttrInfo IconThemeDisplayPropertyInfo where
    type AttrAllowedOps IconThemeDisplayPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint IconThemeDisplayPropertyInfo = IsIconTheme
    type AttrSetTypeConstraint IconThemeDisplayPropertyInfo = Gdk.Display.IsDisplay
    type AttrTransferTypeConstraint IconThemeDisplayPropertyInfo = Gdk.Display.IsDisplay
    type AttrTransferType IconThemeDisplayPropertyInfo = Gdk.Display.Display
    type AttrGetType IconThemeDisplayPropertyInfo = (Maybe Gdk.Display.Display)
    type AttrLabel IconThemeDisplayPropertyInfo = "display"
    type AttrOrigin IconThemeDisplayPropertyInfo = IconTheme
    attrGet = getIconThemeDisplay
    attrSet = setIconThemeDisplay
    attrTransfer _ v = do
        unsafeCastTo Gdk.Display.Display v
    attrConstruct = constructIconThemeDisplay
    attrClear = clearIconThemeDisplay
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.IconTheme.display"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-IconTheme.html#g:attr:display"
        })
#endif
   
   
   
getIconThemeIconNames :: (MonadIO m, IsIconTheme o) => o -> m (Maybe [T.Text])
getIconThemeIconNames :: forall (m :: * -> *) o.
(MonadIO m, IsIconTheme o) =>
o -> m (Maybe [Text])
getIconThemeIconNames o
obj = IO (Maybe [Text]) -> m (Maybe [Text])
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe [Text]) -> m (Maybe [Text]))
-> IO (Maybe [Text]) -> m (Maybe [Text])
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe [Text])
forall a. GObject a => a -> String -> IO (Maybe [Text])
B.Properties.getObjectPropertyStringArray o
obj String
"icon-names"
#if defined(ENABLE_OVERLOADING)
data IconThemeIconNamesPropertyInfo
instance AttrInfo IconThemeIconNamesPropertyInfo where
    type AttrAllowedOps IconThemeIconNamesPropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint IconThemeIconNamesPropertyInfo = IsIconTheme
    type AttrSetTypeConstraint IconThemeIconNamesPropertyInfo = (~) ()
    type AttrTransferTypeConstraint IconThemeIconNamesPropertyInfo = (~) ()
    type AttrTransferType IconThemeIconNamesPropertyInfo = ()
    type AttrGetType IconThemeIconNamesPropertyInfo = (Maybe [T.Text])
    type AttrLabel IconThemeIconNamesPropertyInfo = "icon-names"
    type AttrOrigin IconThemeIconNamesPropertyInfo = IconTheme
    attrGet = getIconThemeIconNames
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.IconTheme.iconNames"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-IconTheme.html#g:attr:iconNames"
        })
#endif
   
   
   
getIconThemeResourcePath :: (MonadIO m, IsIconTheme o) => o -> m (Maybe [T.Text])
getIconThemeResourcePath :: forall (m :: * -> *) o.
(MonadIO m, IsIconTheme o) =>
o -> m (Maybe [Text])
getIconThemeResourcePath o
obj = IO (Maybe [Text]) -> m (Maybe [Text])
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe [Text]) -> m (Maybe [Text]))
-> IO (Maybe [Text]) -> m (Maybe [Text])
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe [Text])
forall a. GObject a => a -> String -> IO (Maybe [Text])
B.Properties.getObjectPropertyStringArray o
obj String
"resource-path"
setIconThemeResourcePath :: (MonadIO m, IsIconTheme o) => o -> [T.Text] -> m ()
setIconThemeResourcePath :: forall (m :: * -> *) o.
(MonadIO m, IsIconTheme o) =>
o -> [Text] -> m ()
setIconThemeResourcePath o
obj [Text]
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe [Text] -> IO ()
forall a. GObject a => a -> String -> Maybe [Text] -> IO ()
B.Properties.setObjectPropertyStringArray o
obj String
"resource-path" ([Text] -> Maybe [Text]
forall a. a -> Maybe a
Just [Text]
val)
constructIconThemeResourcePath :: (IsIconTheme o, MIO.MonadIO m) => [T.Text] -> m (GValueConstruct o)
constructIconThemeResourcePath :: forall o (m :: * -> *).
(IsIconTheme o, MonadIO m) =>
[Text] -> m (GValueConstruct o)
constructIconThemeResourcePath [Text]
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe [Text] -> IO (GValueConstruct o)
forall o. String -> Maybe [Text] -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyStringArray String
"resource-path" ([Text] -> Maybe [Text]
forall a. a -> Maybe a
P.Just [Text]
val)
clearIconThemeResourcePath :: (MonadIO m, IsIconTheme o) => o -> m ()
clearIconThemeResourcePath :: forall (m :: * -> *) o. (MonadIO m, IsIconTheme o) => o -> m ()
clearIconThemeResourcePath o
obj = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe [Text] -> IO ()
forall a. GObject a => a -> String -> Maybe [Text] -> IO ()
B.Properties.setObjectPropertyStringArray o
obj String
"resource-path" (Maybe [Text]
forall a. Maybe a
Nothing :: Maybe [T.Text])
#if defined(ENABLE_OVERLOADING)
data IconThemeResourcePathPropertyInfo
instance AttrInfo IconThemeResourcePathPropertyInfo where
    type AttrAllowedOps IconThemeResourcePathPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint IconThemeResourcePathPropertyInfo = IsIconTheme
    type AttrSetTypeConstraint IconThemeResourcePathPropertyInfo = (~) [T.Text]
    type AttrTransferTypeConstraint IconThemeResourcePathPropertyInfo = (~) [T.Text]
    type AttrTransferType IconThemeResourcePathPropertyInfo = [T.Text]
    type AttrGetType IconThemeResourcePathPropertyInfo = (Maybe [T.Text])
    type AttrLabel IconThemeResourcePathPropertyInfo = "resource-path"
    type AttrOrigin IconThemeResourcePathPropertyInfo = IconTheme
    attrGet = getIconThemeResourcePath
    attrSet = setIconThemeResourcePath
    attrTransfer _ v = do
        return v
    attrConstruct = constructIconThemeResourcePath
    attrClear = clearIconThemeResourcePath
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.IconTheme.resourcePath"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-IconTheme.html#g:attr:resourcePath"
        })
#endif
   
   
   
getIconThemeSearchPath :: (MonadIO m, IsIconTheme o) => o -> m (Maybe [T.Text])
getIconThemeSearchPath :: forall (m :: * -> *) o.
(MonadIO m, IsIconTheme o) =>
o -> m (Maybe [Text])
getIconThemeSearchPath o
obj = IO (Maybe [Text]) -> m (Maybe [Text])
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe [Text]) -> m (Maybe [Text]))
-> IO (Maybe [Text]) -> m (Maybe [Text])
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe [Text])
forall a. GObject a => a -> String -> IO (Maybe [Text])
B.Properties.getObjectPropertyStringArray o
obj String
"search-path"
setIconThemeSearchPath :: (MonadIO m, IsIconTheme o) => o -> [T.Text] -> m ()
setIconThemeSearchPath :: forall (m :: * -> *) o.
(MonadIO m, IsIconTheme o) =>
o -> [Text] -> m ()
setIconThemeSearchPath o
obj [Text]
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe [Text] -> IO ()
forall a. GObject a => a -> String -> Maybe [Text] -> IO ()
B.Properties.setObjectPropertyStringArray o
obj String
"search-path" ([Text] -> Maybe [Text]
forall a. a -> Maybe a
Just [Text]
val)
constructIconThemeSearchPath :: (IsIconTheme o, MIO.MonadIO m) => [T.Text] -> m (GValueConstruct o)
constructIconThemeSearchPath :: forall o (m :: * -> *).
(IsIconTheme o, MonadIO m) =>
[Text] -> m (GValueConstruct o)
constructIconThemeSearchPath [Text]
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe [Text] -> IO (GValueConstruct o)
forall o. String -> Maybe [Text] -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyStringArray String
"search-path" ([Text] -> Maybe [Text]
forall a. a -> Maybe a
P.Just [Text]
val)
clearIconThemeSearchPath :: (MonadIO m, IsIconTheme o) => o -> m ()
clearIconThemeSearchPath :: forall (m :: * -> *) o. (MonadIO m, IsIconTheme o) => o -> m ()
clearIconThemeSearchPath o
obj = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe [Text] -> IO ()
forall a. GObject a => a -> String -> Maybe [Text] -> IO ()
B.Properties.setObjectPropertyStringArray o
obj String
"search-path" (Maybe [Text]
forall a. Maybe a
Nothing :: Maybe [T.Text])
#if defined(ENABLE_OVERLOADING)
data IconThemeSearchPathPropertyInfo
instance AttrInfo IconThemeSearchPathPropertyInfo where
    type AttrAllowedOps IconThemeSearchPathPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint IconThemeSearchPathPropertyInfo = IsIconTheme
    type AttrSetTypeConstraint IconThemeSearchPathPropertyInfo = (~) [T.Text]
    type AttrTransferTypeConstraint IconThemeSearchPathPropertyInfo = (~) [T.Text]
    type AttrTransferType IconThemeSearchPathPropertyInfo = [T.Text]
    type AttrGetType IconThemeSearchPathPropertyInfo = (Maybe [T.Text])
    type AttrLabel IconThemeSearchPathPropertyInfo = "search-path"
    type AttrOrigin IconThemeSearchPathPropertyInfo = IconTheme
    attrGet = getIconThemeSearchPath
    attrSet = setIconThemeSearchPath
    attrTransfer _ v = do
        return v
    attrConstruct = constructIconThemeSearchPath
    attrClear = clearIconThemeSearchPath
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.IconTheme.searchPath"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-IconTheme.html#g:attr:searchPath"
        })
#endif
   
   
   
getIconThemeThemeName :: (MonadIO m, IsIconTheme o) => o -> m (Maybe T.Text)
getIconThemeThemeName :: forall (m :: * -> *) o.
(MonadIO m, IsIconTheme o) =>
o -> m (Maybe Text)
getIconThemeThemeName o
obj = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"theme-name"
setIconThemeThemeName :: (MonadIO m, IsIconTheme o) => o -> T.Text -> m ()
setIconThemeThemeName :: forall (m :: * -> *) o.
(MonadIO m, IsIconTheme o) =>
o -> Text -> m ()
setIconThemeThemeName o
obj Text
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"theme-name" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructIconThemeThemeName :: (IsIconTheme o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructIconThemeThemeName :: forall o (m :: * -> *).
(IsIconTheme o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructIconThemeThemeName Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"theme-name" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
clearIconThemeThemeName :: (MonadIO m, IsIconTheme o) => o -> m ()
clearIconThemeThemeName :: forall (m :: * -> *) o. (MonadIO m, IsIconTheme o) => o -> m ()
clearIconThemeThemeName o
obj = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"theme-name" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)
#if defined(ENABLE_OVERLOADING)
data IconThemeThemeNamePropertyInfo
instance AttrInfo IconThemeThemeNamePropertyInfo where
    type AttrAllowedOps IconThemeThemeNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint IconThemeThemeNamePropertyInfo = IsIconTheme
    type AttrSetTypeConstraint IconThemeThemeNamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint IconThemeThemeNamePropertyInfo = (~) T.Text
    type AttrTransferType IconThemeThemeNamePropertyInfo = T.Text
    type AttrGetType IconThemeThemeNamePropertyInfo = (Maybe T.Text)
    type AttrLabel IconThemeThemeNamePropertyInfo = "theme-name"
    type AttrOrigin IconThemeThemeNamePropertyInfo = IconTheme
    attrGet = getIconThemeThemeName
    attrSet = setIconThemeThemeName
    attrTransfer _ v = do
        return v
    attrConstruct = constructIconThemeThemeName
    attrClear = clearIconThemeThemeName
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.IconTheme.themeName"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-IconTheme.html#g:attr:themeName"
        })
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList IconTheme
type instance O.AttributeList IconTheme = IconThemeAttributeList
type IconThemeAttributeList = ('[ '("display", IconThemeDisplayPropertyInfo), '("iconNames", IconThemeIconNamesPropertyInfo), '("resourcePath", IconThemeResourcePathPropertyInfo), '("searchPath", IconThemeSearchPathPropertyInfo), '("themeName", IconThemeThemeNamePropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
iconThemeDisplay :: AttrLabelProxy "display"
iconThemeDisplay = AttrLabelProxy
iconThemeIconNames :: AttrLabelProxy "iconNames"
iconThemeIconNames = AttrLabelProxy
iconThemeResourcePath :: AttrLabelProxy "resourcePath"
iconThemeResourcePath = AttrLabelProxy
iconThemeSearchPath :: AttrLabelProxy "searchPath"
iconThemeSearchPath = AttrLabelProxy
iconThemeThemeName :: AttrLabelProxy "themeName"
iconThemeThemeName = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList IconTheme = IconThemeSignalList
type IconThemeSignalList = ('[ '("changed", IconThemeChangedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "gtk_icon_theme_new" gtk_icon_theme_new :: 
    IO (Ptr IconTheme)
iconThemeNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m IconTheme
    
iconThemeNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m IconTheme
iconThemeNew  = IO IconTheme -> m IconTheme
forall a. IO a -> m a
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 Text
"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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return IconTheme
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_icon_theme_add_resource_path" gtk_icon_theme_add_resource_path :: 
    Ptr IconTheme ->                        
    CString ->                              
    IO ()
iconThemeAddResourcePath ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
    a
    
    -> T.Text
    
    -> m ()
iconThemeAddResourcePath :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIconTheme a) =>
a -> Text -> m ()
iconThemeAddResourcePath a
self Text
path = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr IconTheme
self' <- a -> IO (Ptr IconTheme)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
path' <- Text -> IO CString
textToCString Text
path
    Ptr IconTheme -> CString -> IO ()
gtk_icon_theme_add_resource_path Ptr IconTheme
self' CString
path'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
    () -> IO ()
forall a. a -> IO a
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.OverloadedMethod IconThemeAddResourcePathMethodInfo a signature where
    overloadedMethod = iconThemeAddResourcePath
instance O.OverloadedMethodInfo IconThemeAddResourcePathMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.IconTheme.iconThemeAddResourcePath",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-IconTheme.html#v:iconThemeAddResourcePath"
        })
#endif
foreign import ccall "gtk_icon_theme_add_search_path" gtk_icon_theme_add_search_path :: 
    Ptr IconTheme ->                        
    CString ->                              
    IO ()
iconThemeAddSearchPath ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
    a
    
    -> [Char]
    
    -> m ()
iconThemeAddSearchPath :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIconTheme a) =>
a -> String -> m ()
iconThemeAddSearchPath a
self String
path = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr IconTheme
self' <- a -> IO (Ptr IconTheme)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
path' <- String -> IO CString
stringToCString String
path
    Ptr IconTheme -> CString -> IO ()
gtk_icon_theme_add_search_path Ptr IconTheme
self' CString
path'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data IconThemeAddSearchPathMethodInfo
instance (signature ~ ([Char] -> m ()), MonadIO m, IsIconTheme a) => O.OverloadedMethod IconThemeAddSearchPathMethodInfo a signature where
    overloadedMethod = iconThemeAddSearchPath
instance O.OverloadedMethodInfo IconThemeAddSearchPathMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.IconTheme.iconThemeAddSearchPath",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-IconTheme.html#v:iconThemeAddSearchPath"
        })
#endif
foreign import ccall "gtk_icon_theme_get_display" gtk_icon_theme_get_display :: 
    Ptr IconTheme ->                        
    IO (Ptr Gdk.Display.Display)
iconThemeGetDisplay ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
    a
    
    -> m (Maybe Gdk.Display.Display)
    
iconThemeGetDisplay :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIconTheme a) =>
a -> m (Maybe Display)
iconThemeGetDisplay a
self = IO (Maybe Display) -> m (Maybe Display)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Display) -> m (Maybe Display))
-> IO (Maybe Display) -> m (Maybe Display)
forall a b. (a -> b) -> a -> b
$ do
    Ptr IconTheme
self' <- a -> IO (Ptr IconTheme)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Display
result <- Ptr IconTheme -> IO (Ptr Display)
gtk_icon_theme_get_display Ptr IconTheme
self'
    Maybe Display
maybeResult <- Ptr Display -> (Ptr Display -> IO Display) -> IO (Maybe Display)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Display
result ((Ptr Display -> IO Display) -> IO (Maybe Display))
-> (Ptr Display -> IO Display) -> IO (Maybe Display)
forall a b. (a -> b) -> a -> b
$ \Ptr Display
result' -> do
        Display
result'' <- ((ManagedPtr Display -> Display) -> Ptr Display -> IO Display
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Display -> Display
Gdk.Display.Display) Ptr Display
result'
        Display -> IO Display
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Display
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe Display -> IO (Maybe Display)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Display
maybeResult
#if defined(ENABLE_OVERLOADING)
data IconThemeGetDisplayMethodInfo
instance (signature ~ (m (Maybe Gdk.Display.Display)), MonadIO m, IsIconTheme a) => O.OverloadedMethod IconThemeGetDisplayMethodInfo a signature where
    overloadedMethod = iconThemeGetDisplay
instance O.OverloadedMethodInfo IconThemeGetDisplayMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.IconTheme.iconThemeGetDisplay",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-IconTheme.html#v:iconThemeGetDisplay"
        })
#endif
foreign import ccall "gtk_icon_theme_get_icon_names" gtk_icon_theme_get_icon_names :: 
    Ptr IconTheme ->                        
    IO (Ptr CString)
iconThemeGetIconNames ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
    a
    
    -> m [T.Text]
    
    
    
iconThemeGetIconNames :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIconTheme a) =>
a -> m [Text]
iconThemeGetIconNames a
self = IO [Text] -> m [Text]
forall a. IO a -> m a
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
self' <- a -> IO (Ptr IconTheme)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr CString
result <- Ptr IconTheme -> IO (Ptr CString)
gtk_icon_theme_get_icon_names Ptr IconTheme
self'
    Text -> Ptr CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iconThemeGetIconNames" Ptr CString
result
    [Text]
result' <- HasCallStack => Ptr CString -> IO [Text]
Ptr CString -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr CString
result
    (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
result
    Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    [Text] -> IO [Text]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result'
#if defined(ENABLE_OVERLOADING)
data IconThemeGetIconNamesMethodInfo
instance (signature ~ (m [T.Text]), MonadIO m, IsIconTheme a) => O.OverloadedMethod IconThemeGetIconNamesMethodInfo a signature where
    overloadedMethod = iconThemeGetIconNames
instance O.OverloadedMethodInfo IconThemeGetIconNamesMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.IconTheme.iconThemeGetIconNames",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-IconTheme.html#v:iconThemeGetIconNames"
        })
#endif
foreign import ccall "gtk_icon_theme_get_icon_sizes" gtk_icon_theme_get_icon_sizes :: 
    Ptr IconTheme ->                        
    CString ->                              
    IO (Ptr Int32)
iconThemeGetIconSizes ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
    a
    
    -> T.Text
    
    -> m [Int32]
    
    
    
    
iconThemeGetIconSizes :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIconTheme a) =>
a -> Text -> m [Int32]
iconThemeGetIconSizes a
self Text
iconName = IO [Int32] -> m [Int32]
forall a. IO a -> m a
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
self' <- a -> IO (Ptr IconTheme)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    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
self' CString
iconName'
    Text -> Ptr Int32 -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"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
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
iconName'
    [Int32] -> IO [Int32]
forall a. a -> IO a
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.OverloadedMethod IconThemeGetIconSizesMethodInfo a signature where
    overloadedMethod = iconThemeGetIconSizes
instance O.OverloadedMethodInfo IconThemeGetIconSizesMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.IconTheme.iconThemeGetIconSizes",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-IconTheme.html#v:iconThemeGetIconSizes"
        })
#endif
foreign import ccall "gtk_icon_theme_get_resource_path" gtk_icon_theme_get_resource_path :: 
    Ptr IconTheme ->                        
    IO (Ptr CString)
iconThemeGetResourcePath ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
    a
    
    -> m (Maybe [T.Text])
    
    
iconThemeGetResourcePath :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIconTheme a) =>
a -> m (Maybe [Text])
iconThemeGetResourcePath a
self = IO (Maybe [Text]) -> m (Maybe [Text])
forall a. IO a -> m a
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
self' <- a -> IO (Ptr IconTheme)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr CString
result <- Ptr IconTheme -> IO (Ptr CString)
gtk_icon_theme_get_resource_path Ptr IconTheme
self'
    Maybe [Text]
maybeResult <- Ptr CString -> (Ptr CString -> IO [Text]) -> IO (Maybe [Text])
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr CString
result ((Ptr CString -> IO [Text]) -> IO (Maybe [Text]))
-> (Ptr CString -> IO [Text]) -> IO (Maybe [Text])
forall a b. (a -> b) -> a -> b
$ \Ptr CString
result' -> do
        [Text]
result'' <- HasCallStack => Ptr CString -> IO [Text]
Ptr CString -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr CString
result'
        (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
result'
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
result'
        [Text] -> IO [Text]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe [Text] -> IO (Maybe [Text])
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe [Text]
maybeResult
#if defined(ENABLE_OVERLOADING)
data IconThemeGetResourcePathMethodInfo
instance (signature ~ (m (Maybe [T.Text])), MonadIO m, IsIconTheme a) => O.OverloadedMethod IconThemeGetResourcePathMethodInfo a signature where
    overloadedMethod = iconThemeGetResourcePath
instance O.OverloadedMethodInfo IconThemeGetResourcePathMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.IconTheme.iconThemeGetResourcePath",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-IconTheme.html#v:iconThemeGetResourcePath"
        })
#endif
foreign import ccall "gtk_icon_theme_get_search_path" gtk_icon_theme_get_search_path :: 
    Ptr IconTheme ->                        
    IO (Ptr CString)
iconThemeGetSearchPath ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
    a
    
    -> m (Maybe [[Char]])
    
    
iconThemeGetSearchPath :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIconTheme a) =>
a -> m (Maybe [String])
iconThemeGetSearchPath a
self = IO (Maybe [String]) -> m (Maybe [String])
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe [String]) -> m (Maybe [String]))
-> IO (Maybe [String]) -> m (Maybe [String])
forall a b. (a -> b) -> a -> b
$ do
    Ptr IconTheme
self' <- a -> IO (Ptr IconTheme)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr CString
result <- Ptr IconTheme -> IO (Ptr CString)
gtk_icon_theme_get_search_path Ptr IconTheme
self'
    Maybe [String]
maybeResult <- Ptr CString -> (Ptr CString -> IO [String]) -> IO (Maybe [String])
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr CString
result ((Ptr CString -> IO [String]) -> IO (Maybe [String]))
-> (Ptr CString -> IO [String]) -> IO (Maybe [String])
forall a b. (a -> b) -> a -> b
$ \Ptr CString
result' -> do
        [String]
result'' <- HasCallStack => Ptr CString -> IO [String]
Ptr CString -> IO [String]
unpackZeroTerminatedFileNameArray Ptr CString
result'
        (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
result'
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
result'
        [String] -> IO [String]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [String]
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe [String] -> IO (Maybe [String])
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe [String]
maybeResult
#if defined(ENABLE_OVERLOADING)
data IconThemeGetSearchPathMethodInfo
instance (signature ~ (m (Maybe [[Char]])), MonadIO m, IsIconTheme a) => O.OverloadedMethod IconThemeGetSearchPathMethodInfo a signature where
    overloadedMethod = iconThemeGetSearchPath
instance O.OverloadedMethodInfo IconThemeGetSearchPathMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.IconTheme.iconThemeGetSearchPath",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-IconTheme.html#v:iconThemeGetSearchPath"
        })
#endif
foreign import ccall "gtk_icon_theme_get_theme_name" gtk_icon_theme_get_theme_name :: 
    Ptr IconTheme ->                        
    IO CString
iconThemeGetThemeName ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
    a
    
    -> m T.Text
iconThemeGetThemeName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIconTheme a) =>
a -> m Text
iconThemeGetThemeName a
self = IO Text -> m Text
forall a. IO a -> m a
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
self' <- a -> IO (Ptr IconTheme)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr IconTheme -> IO CString
gtk_icon_theme_get_theme_name Ptr IconTheme
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iconThemeGetThemeName" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data IconThemeGetThemeNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsIconTheme a) => O.OverloadedMethod IconThemeGetThemeNameMethodInfo a signature where
    overloadedMethod = iconThemeGetThemeName
instance O.OverloadedMethodInfo IconThemeGetThemeNameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.IconTheme.iconThemeGetThemeName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-IconTheme.html#v:iconThemeGetThemeName"
        })
#endif
foreign import ccall "gtk_icon_theme_has_gicon" gtk_icon_theme_has_gicon :: 
    Ptr IconTheme ->                        
    Ptr Gio.Icon.Icon ->                    
    IO CInt
iconThemeHasGicon ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconTheme a, Gio.Icon.IsIcon b) =>
    a
    
    -> b
    
    -> m Bool
    
iconThemeHasGicon :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsIconTheme a, IsIcon b) =>
a -> b -> m Bool
iconThemeHasGicon a
self b
gicon = IO Bool -> m Bool
forall a. IO a -> m a
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
self' <- a -> IO (Ptr IconTheme)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Icon
gicon' <- b -> IO (Ptr Icon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
gicon
    CInt
result <- Ptr IconTheme -> Ptr Icon -> IO CInt
gtk_icon_theme_has_gicon Ptr IconTheme
self' Ptr Icon
gicon'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
gicon
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data IconThemeHasGiconMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsIconTheme a, Gio.Icon.IsIcon b) => O.OverloadedMethod IconThemeHasGiconMethodInfo a signature where
    overloadedMethod = iconThemeHasGicon
instance O.OverloadedMethodInfo IconThemeHasGiconMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.IconTheme.iconThemeHasGicon",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-IconTheme.html#v:iconThemeHasGicon"
        })
#endif
foreign import ccall "gtk_icon_theme_has_icon" gtk_icon_theme_has_icon :: 
    Ptr IconTheme ->                        
    CString ->                              
    IO CInt
iconThemeHasIcon ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
    a
    
    -> T.Text
    
    -> m Bool
    
    
iconThemeHasIcon :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIconTheme a) =>
a -> Text -> m Bool
iconThemeHasIcon a
self Text
iconName = IO Bool -> m Bool
forall a. IO a -> m a
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
self' <- a -> IO (Ptr IconTheme)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
iconName' <- Text -> IO CString
textToCString Text
iconName
    CInt
result <- Ptr IconTheme -> CString -> IO CInt
gtk_icon_theme_has_icon Ptr IconTheme
self' CString
iconName'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
iconName'
    Bool -> IO Bool
forall a. a -> IO a
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.OverloadedMethod IconThemeHasIconMethodInfo a signature where
    overloadedMethod = iconThemeHasIcon
instance O.OverloadedMethodInfo IconThemeHasIconMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.IconTheme.iconThemeHasIcon",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-IconTheme.html#v:iconThemeHasIcon"
        })
#endif
foreign import ccall "gtk_icon_theme_lookup_by_gicon" gtk_icon_theme_lookup_by_gicon :: 
    Ptr IconTheme ->                        
    Ptr Gio.Icon.Icon ->                    
    Int32 ->                                
    Int32 ->                                
    CUInt ->                                
    CUInt ->                                
    IO (Ptr Gtk.IconPaintable.IconPaintable)
iconThemeLookupByGicon ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconTheme a, Gio.Icon.IsIcon b) =>
    a
    
    -> b
    
    -> Int32
    
    -> Int32
    
    -> Gtk.Enums.TextDirection
    
    -> [Gtk.Flags.IconLookupFlags]
    
    -> m Gtk.IconPaintable.IconPaintable
    
    
iconThemeLookupByGicon :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsIconTheme a, IsIcon b) =>
a
-> b
-> Int32
-> Int32
-> TextDirection
-> [IconLookupFlags]
-> m IconPaintable
iconThemeLookupByGicon a
self b
icon Int32
size Int32
scale TextDirection
direction [IconLookupFlags]
flags = IO IconPaintable -> m IconPaintable
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO IconPaintable -> m IconPaintable)
-> IO IconPaintable -> m IconPaintable
forall a b. (a -> b) -> a -> b
$ do
    Ptr IconTheme
self' <- a -> IO (Ptr IconTheme)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Icon
icon' <- b -> IO (Ptr Icon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
icon
    let direction' :: CUInt
direction' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (TextDirection -> Int) -> TextDirection -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextDirection -> Int
forall a. Enum a => a -> Int
fromEnum) TextDirection
direction
    let flags' :: CUInt
flags' = [IconLookupFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [IconLookupFlags]
flags
    Ptr IconPaintable
result <- Ptr IconTheme
-> Ptr Icon
-> Int32
-> Int32
-> CUInt
-> CUInt
-> IO (Ptr IconPaintable)
gtk_icon_theme_lookup_by_gicon Ptr IconTheme
self' Ptr Icon
icon' Int32
size Int32
scale CUInt
direction' CUInt
flags'
    Text -> Ptr IconPaintable -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iconThemeLookupByGicon" Ptr IconPaintable
result
    IconPaintable
result' <- ((ManagedPtr IconPaintable -> IconPaintable)
-> Ptr IconPaintable -> IO IconPaintable
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr IconPaintable -> IconPaintable
Gtk.IconPaintable.IconPaintable) Ptr IconPaintable
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
icon
    IconPaintable -> IO IconPaintable
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return IconPaintable
result'
#if defined(ENABLE_OVERLOADING)
data IconThemeLookupByGiconMethodInfo
instance (signature ~ (b -> Int32 -> Int32 -> Gtk.Enums.TextDirection -> [Gtk.Flags.IconLookupFlags] -> m Gtk.IconPaintable.IconPaintable), MonadIO m, IsIconTheme a, Gio.Icon.IsIcon b) => O.OverloadedMethod IconThemeLookupByGiconMethodInfo a signature where
    overloadedMethod = iconThemeLookupByGicon
instance O.OverloadedMethodInfo IconThemeLookupByGiconMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.IconTheme.iconThemeLookupByGicon",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-IconTheme.html#v:iconThemeLookupByGicon"
        })
#endif
foreign import ccall "gtk_icon_theme_lookup_icon" gtk_icon_theme_lookup_icon :: 
    Ptr IconTheme ->                        
    CString ->                              
    Ptr CString ->                          
    Int32 ->                                
    Int32 ->                                
    CUInt ->                                
    CUInt ->                                
    IO (Ptr Gtk.IconPaintable.IconPaintable)
iconThemeLookupIcon ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
    a
    
    -> T.Text
    
    -> Maybe ([T.Text])
    -> Int32
    
    -> Int32
    
    -> Gtk.Enums.TextDirection
    
    -> [Gtk.Flags.IconLookupFlags]
    
    -> m Gtk.IconPaintable.IconPaintable
    
    
iconThemeLookupIcon :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIconTheme a) =>
a
-> Text
-> Maybe [Text]
-> Int32
-> Int32
-> TextDirection
-> [IconLookupFlags]
-> m IconPaintable
iconThemeLookupIcon a
self Text
iconName Maybe [Text]
fallbacks Int32
size Int32
scale TextDirection
direction [IconLookupFlags]
flags = IO IconPaintable -> m IconPaintable
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO IconPaintable -> m IconPaintable)
-> IO IconPaintable -> m IconPaintable
forall a b. (a -> b) -> a -> b
$ do
    Ptr IconTheme
self' <- a -> IO (Ptr IconTheme)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
iconName' <- Text -> IO CString
textToCString Text
iconName
    Ptr CString
maybeFallbacks <- case Maybe [Text]
fallbacks of
        Maybe [Text]
Nothing -> Ptr CString -> IO (Ptr CString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
forall a. Ptr a
nullPtr
        Just [Text]
jFallbacks -> do
            Ptr CString
jFallbacks' <- [Text] -> IO (Ptr CString)
packZeroTerminatedUTF8CArray [Text]
jFallbacks
            Ptr CString -> IO (Ptr CString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
jFallbacks'
    let direction' :: CUInt
direction' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (TextDirection -> Int) -> TextDirection -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextDirection -> Int
forall a. Enum a => a -> Int
fromEnum) TextDirection
direction
    let flags' :: CUInt
flags' = [IconLookupFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [IconLookupFlags]
flags
    Ptr IconPaintable
result <- Ptr IconTheme
-> CString
-> Ptr CString
-> Int32
-> Int32
-> CUInt
-> CUInt
-> IO (Ptr IconPaintable)
gtk_icon_theme_lookup_icon Ptr IconTheme
self' CString
iconName' Ptr CString
maybeFallbacks Int32
size Int32
scale CUInt
direction' CUInt
flags'
    Text -> Ptr IconPaintable -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iconThemeLookupIcon" Ptr IconPaintable
result
    IconPaintable
result' <- ((ManagedPtr IconPaintable -> IconPaintable)
-> Ptr IconPaintable -> IO IconPaintable
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr IconPaintable -> IconPaintable
Gtk.IconPaintable.IconPaintable) Ptr IconPaintable
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
iconName'
    (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
maybeFallbacks
    Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeFallbacks
    IconPaintable -> IO IconPaintable
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return IconPaintable
result'
#if defined(ENABLE_OVERLOADING)
data IconThemeLookupIconMethodInfo
instance (signature ~ (T.Text -> Maybe ([T.Text]) -> Int32 -> Int32 -> Gtk.Enums.TextDirection -> [Gtk.Flags.IconLookupFlags] -> m Gtk.IconPaintable.IconPaintable), MonadIO m, IsIconTheme a) => O.OverloadedMethod IconThemeLookupIconMethodInfo a signature where
    overloadedMethod = iconThemeLookupIcon
instance O.OverloadedMethodInfo IconThemeLookupIconMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.IconTheme.iconThemeLookupIcon",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-IconTheme.html#v:iconThemeLookupIcon"
        })
#endif
foreign import ccall "gtk_icon_theme_set_resource_path" gtk_icon_theme_set_resource_path :: 
    Ptr IconTheme ->                        
    Ptr CString ->                          
    IO ()
iconThemeSetResourcePath ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
    a
    
    -> Maybe ([T.Text])
    
    
    
    -> m ()
iconThemeSetResourcePath :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIconTheme a) =>
a -> Maybe [Text] -> m ()
iconThemeSetResourcePath a
self Maybe [Text]
path = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr IconTheme
self' <- a -> IO (Ptr IconTheme)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr CString
maybePath <- case Maybe [Text]
path of
        Maybe [Text]
Nothing -> Ptr CString -> IO (Ptr CString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
forall a. Ptr a
nullPtr
        Just [Text]
jPath -> do
            Ptr CString
jPath' <- [Text] -> IO (Ptr CString)
packZeroTerminatedUTF8CArray [Text]
jPath
            Ptr CString -> IO (Ptr CString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
jPath'
    Ptr IconTheme -> Ptr CString -> IO ()
gtk_icon_theme_set_resource_path Ptr IconTheme
self' Ptr CString
maybePath
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    (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
maybePath
    Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybePath
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data IconThemeSetResourcePathMethodInfo
instance (signature ~ (Maybe ([T.Text]) -> m ()), MonadIO m, IsIconTheme a) => O.OverloadedMethod IconThemeSetResourcePathMethodInfo a signature where
    overloadedMethod = iconThemeSetResourcePath
instance O.OverloadedMethodInfo IconThemeSetResourcePathMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.IconTheme.iconThemeSetResourcePath",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-IconTheme.html#v:iconThemeSetResourcePath"
        })
#endif
foreign import ccall "gtk_icon_theme_set_search_path" gtk_icon_theme_set_search_path :: 
    Ptr IconTheme ->                        
    Ptr CString ->                          
    IO ()
iconThemeSetSearchPath ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
    a
    
    -> Maybe ([[Char]])
    
    
    -> m ()
iconThemeSetSearchPath :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIconTheme a) =>
a -> Maybe [String] -> m ()
iconThemeSetSearchPath a
self Maybe [String]
path = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr IconTheme
self' <- a -> IO (Ptr IconTheme)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr CString
maybePath <- case Maybe [String]
path of
        Maybe [String]
Nothing -> Ptr CString -> IO (Ptr CString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
forall a. Ptr a
nullPtr
        Just [String]
jPath -> do
            Ptr CString
jPath' <- [String] -> IO (Ptr CString)
packZeroTerminatedFileNameArray [String]
jPath
            Ptr CString -> IO (Ptr CString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
jPath'
    Ptr IconTheme -> Ptr CString -> IO ()
gtk_icon_theme_set_search_path Ptr IconTheme
self' Ptr CString
maybePath
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    (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
maybePath
    Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybePath
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data IconThemeSetSearchPathMethodInfo
instance (signature ~ (Maybe ([[Char]]) -> m ()), MonadIO m, IsIconTheme a) => O.OverloadedMethod IconThemeSetSearchPathMethodInfo a signature where
    overloadedMethod = iconThemeSetSearchPath
instance O.OverloadedMethodInfo IconThemeSetSearchPathMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.IconTheme.iconThemeSetSearchPath",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-IconTheme.html#v:iconThemeSetSearchPath"
        })
#endif
foreign import ccall "gtk_icon_theme_set_theme_name" gtk_icon_theme_set_theme_name :: 
    Ptr IconTheme ->                        
    CString ->                              
    IO ()
iconThemeSetThemeName ::
    (B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
    a
    
    -> Maybe (T.Text)
    
    
    -> m ()
iconThemeSetThemeName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIconTheme a) =>
a -> Maybe Text -> m ()
iconThemeSetThemeName a
self Maybe Text
themeName = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr IconTheme
self' <- a -> IO (Ptr IconTheme)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
maybeThemeName <- case Maybe Text
themeName of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jThemeName -> do
            CString
jThemeName' <- Text -> IO CString
textToCString Text
jThemeName
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jThemeName'
    Ptr IconTheme -> CString -> IO ()
gtk_icon_theme_set_theme_name Ptr IconTheme
self' CString
maybeThemeName
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeThemeName
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data IconThemeSetThemeNameMethodInfo
instance (signature ~ (Maybe (T.Text) -> m ()), MonadIO m, IsIconTheme a) => O.OverloadedMethod IconThemeSetThemeNameMethodInfo a signature where
    overloadedMethod = iconThemeSetThemeName
instance O.OverloadedMethodInfo IconThemeSetThemeNameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.IconTheme.iconThemeSetThemeName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-IconTheme.html#v:iconThemeSetThemeName"
        })
#endif
foreign import ccall "gtk_icon_theme_get_for_display" gtk_icon_theme_get_for_display :: 
    Ptr Gdk.Display.Display ->              
    IO (Ptr IconTheme)
iconThemeGetForDisplay ::
    (B.CallStack.HasCallStack, MonadIO m, Gdk.Display.IsDisplay a) =>
    a
    
    -> m IconTheme
    
    
    
iconThemeGetForDisplay :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> m IconTheme
iconThemeGetForDisplay a
display = IO IconTheme -> m IconTheme
forall a. IO a -> m a
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 Display
display' <- a -> IO (Ptr Display)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
display
    Ptr IconTheme
result <- Ptr Display -> IO (Ptr IconTheme)
gtk_icon_theme_get_for_display Ptr Display
display'
    Text -> Ptr IconTheme -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iconThemeGetForDisplay" 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
display
    IconTheme -> IO IconTheme
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return IconTheme
result'
#if defined(ENABLE_OVERLOADING)
#endif