{-# LANGUAGE 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 ,
noIconTheme ,
#if defined(ENABLE_OVERLOADING)
ResolveIconThemeMethod ,
#endif
iconThemeAddBuiltinIcon ,
#if defined(ENABLE_OVERLOADING)
IconThemeAddResourcePathMethodInfo ,
#endif
iconThemeAddResourcePath ,
#if defined(ENABLE_OVERLOADING)
IconThemeAppendSearchPathMethodInfo ,
#endif
iconThemeAppendSearchPath ,
#if defined(ENABLE_OVERLOADING)
IconThemeChooseIconMethodInfo ,
#endif
iconThemeChooseIcon ,
#if defined(ENABLE_OVERLOADING)
IconThemeChooseIconForScaleMethodInfo ,
#endif
iconThemeChooseIconForScale ,
iconThemeGetDefault ,
#if defined(ENABLE_OVERLOADING)
IconThemeGetExampleIconNameMethodInfo ,
#endif
iconThemeGetExampleIconName ,
iconThemeGetForScreen ,
#if defined(ENABLE_OVERLOADING)
IconThemeGetIconSizesMethodInfo ,
#endif
iconThemeGetIconSizes ,
#if defined(ENABLE_OVERLOADING)
IconThemeGetSearchPathMethodInfo ,
#endif
iconThemeGetSearchPath ,
#if defined(ENABLE_OVERLOADING)
IconThemeHasIconMethodInfo ,
#endif
iconThemeHasIcon ,
#if defined(ENABLE_OVERLOADING)
IconThemeListContextsMethodInfo ,
#endif
iconThemeListContexts ,
#if defined(ENABLE_OVERLOADING)
IconThemeListIconsMethodInfo ,
#endif
iconThemeListIcons ,
#if defined(ENABLE_OVERLOADING)
IconThemeLoadIconMethodInfo ,
#endif
iconThemeLoadIcon ,
#if defined(ENABLE_OVERLOADING)
IconThemeLoadIconForScaleMethodInfo ,
#endif
iconThemeLoadIconForScale ,
#if defined(ENABLE_OVERLOADING)
IconThemeLoadSurfaceMethodInfo ,
#endif
iconThemeLoadSurface ,
#if defined(ENABLE_OVERLOADING)
IconThemeLookupByGiconMethodInfo ,
#endif
iconThemeLookupByGicon ,
#if defined(ENABLE_OVERLOADING)
IconThemeLookupByGiconForScaleMethodInfo,
#endif
iconThemeLookupByGiconForScale ,
#if defined(ENABLE_OVERLOADING)
IconThemeLookupIconMethodInfo ,
#endif
iconThemeLookupIcon ,
#if defined(ENABLE_OVERLOADING)
IconThemeLookupIconForScaleMethodInfo ,
#endif
iconThemeLookupIconForScale ,
iconThemeNew ,
#if defined(ENABLE_OVERLOADING)
IconThemePrependSearchPathMethodInfo ,
#endif
iconThemePrependSearchPath ,
#if defined(ENABLE_OVERLOADING)
IconThemeRescanIfNeededMethodInfo ,
#endif
iconThemeRescanIfNeeded ,
#if defined(ENABLE_OVERLOADING)
IconThemeSetCustomThemeMethodInfo ,
#endif
iconThemeSetCustomTheme ,
#if defined(ENABLE_OVERLOADING)
IconThemeSetScreenMethodInfo ,
#endif
iconThemeSetScreen ,
#if defined(ENABLE_OVERLOADING)
IconThemeSetSearchPathMethodInfo ,
#endif
iconThemeSetSearchPath ,
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
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
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
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]
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
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
type IconThemeChangedCallback =
IO ()
noIconThemeChangedCallback :: Maybe IconThemeChangedCallback
noIconThemeChangedCallback :: Maybe (IO ())
noIconThemeChangedCallback = Maybe (IO ())
forall a. Maybe a
Nothing
type C_IconThemeChangedCallback =
Ptr () ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_IconThemeChangedCallback :: C_IconThemeChangedCallback -> IO (FunPtr C_IconThemeChangedCallback)
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_IconThemeChangedCallback ::
IconThemeChangedCallback ->
C_IconThemeChangedCallback
wrap_IconThemeChangedCallback :: IO () -> C_IconThemeChangedCallback
wrap_IconThemeChangedCallback _cb :: IO ()
_cb _ _ = do
IO ()
_cb
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
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
foreign import ccall "gtk_icon_theme_new" gtk_icon_theme_new ::
IO (Ptr IconTheme)
iconThemeNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
m IconTheme
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
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 :: 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
foreign import ccall "gtk_icon_theme_append_search_path" gtk_icon_theme_append_search_path ::
Ptr IconTheme ->
CString ->
IO ()
iconThemeAppendSearchPath ::
(B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
a
-> [Char]
-> 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
foreign import ccall "gtk_icon_theme_choose_icon" gtk_icon_theme_choose_icon ::
Ptr IconTheme ->
Ptr CString ->
Int32 ->
CUInt ->
IO (Ptr Gtk.IconInfo.IconInfo)
iconThemeChooseIcon ::
(B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
a
-> [T.Text]
-> Int32
-> [Gtk.Flags.IconLookupFlags]
-> m (Maybe Gtk.IconInfo.IconInfo)
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
foreign import ccall "gtk_icon_theme_choose_icon_for_scale" gtk_icon_theme_choose_icon_for_scale ::
Ptr IconTheme ->
Ptr CString ->
Int32 ->
Int32 ->
CUInt ->
IO (Ptr Gtk.IconInfo.IconInfo)
iconThemeChooseIconForScale ::
(B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
a
-> [T.Text]
-> Int32
-> Int32
-> [Gtk.Flags.IconLookupFlags]
-> m (Maybe Gtk.IconInfo.IconInfo)
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
foreign import ccall "gtk_icon_theme_get_example_icon_name" gtk_icon_theme_get_example_icon_name ::
Ptr IconTheme ->
IO CString
iconThemeGetExampleIconName ::
(B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
a
-> m (Maybe T.Text)
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
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 :: 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
foreign import ccall "gtk_icon_theme_get_search_path" gtk_icon_theme_get_search_path ::
Ptr IconTheme ->
Ptr (Ptr CString) ->
Ptr Int32 ->
IO ()
iconThemeGetSearchPath ::
(B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
a
-> 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
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 :: 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
foreign import ccall "gtk_icon_theme_list_contexts" gtk_icon_theme_list_contexts ::
Ptr IconTheme ->
IO (Ptr (GList CString))
iconThemeListContexts ::
(B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
a
-> m [T.Text]
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
foreign import ccall "gtk_icon_theme_list_icons" gtk_icon_theme_list_icons ::
Ptr IconTheme ->
CString ->
IO (Ptr (GList CString))
iconThemeListIcons ::
(B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
a
-> Maybe (T.Text)
-> m [T.Text]
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
foreign import ccall "gtk_icon_theme_load_icon" gtk_icon_theme_load_icon ::
Ptr IconTheme ->
CString ->
Int32 ->
CUInt ->
Ptr (Ptr GError) ->
IO (Ptr GdkPixbuf.Pixbuf.Pixbuf)
iconThemeLoadIcon ::
(B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
a
-> T.Text
-> Int32
-> [Gtk.Flags.IconLookupFlags]
-> m (Maybe GdkPixbuf.Pixbuf.Pixbuf)
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
foreign import ccall "gtk_icon_theme_load_icon_for_scale" gtk_icon_theme_load_icon_for_scale ::
Ptr IconTheme ->
CString ->
Int32 ->
Int32 ->
CUInt ->
Ptr (Ptr GError) ->
IO (Ptr GdkPixbuf.Pixbuf.Pixbuf)
iconThemeLoadIconForScale ::
(B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
a
-> T.Text
-> Int32
-> Int32
-> [Gtk.Flags.IconLookupFlags]
-> m (Maybe GdkPixbuf.Pixbuf.Pixbuf)
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
foreign import ccall "gtk_icon_theme_load_surface" gtk_icon_theme_load_surface ::
Ptr IconTheme ->
CString ->
Int32 ->
Int32 ->
Ptr Gdk.Window.Window ->
CUInt ->
Ptr (Ptr GError) ->
IO (Ptr Cairo.Surface.Surface)
iconThemeLoadSurface ::
(B.CallStack.HasCallStack, MonadIO m, IsIconTheme a, Gdk.Window.IsWindow b) =>
a
-> T.Text
-> Int32
-> Int32
-> Maybe (b)
-> [Gtk.Flags.IconLookupFlags]
-> m (Maybe Cairo.Surface.Surface)
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
foreign import ccall "gtk_icon_theme_lookup_by_gicon" gtk_icon_theme_lookup_by_gicon ::
Ptr IconTheme ->
Ptr Gio.Icon.Icon ->
Int32 ->
CUInt ->
IO (Ptr Gtk.IconInfo.IconInfo)
iconThemeLookupByGicon ::
(B.CallStack.HasCallStack, MonadIO m, IsIconTheme a, Gio.Icon.IsIcon b) =>
a
-> b
-> Int32
-> [Gtk.Flags.IconLookupFlags]
-> m (Maybe Gtk.IconInfo.IconInfo)
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
foreign import ccall "gtk_icon_theme_lookup_by_gicon_for_scale" gtk_icon_theme_lookup_by_gicon_for_scale ::
Ptr IconTheme ->
Ptr Gio.Icon.Icon ->
Int32 ->
Int32 ->
CUInt ->
IO (Ptr Gtk.IconInfo.IconInfo)
iconThemeLookupByGiconForScale ::
(B.CallStack.HasCallStack, MonadIO m, IsIconTheme a, Gio.Icon.IsIcon b) =>
a
-> b
-> Int32
-> Int32
-> [Gtk.Flags.IconLookupFlags]
-> m (Maybe Gtk.IconInfo.IconInfo)
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
foreign import ccall "gtk_icon_theme_lookup_icon" gtk_icon_theme_lookup_icon ::
Ptr IconTheme ->
CString ->
Int32 ->
CUInt ->
IO (Ptr Gtk.IconInfo.IconInfo)
iconThemeLookupIcon ::
(B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
a
-> T.Text
-> Int32
-> [Gtk.Flags.IconLookupFlags]
-> m (Maybe Gtk.IconInfo.IconInfo)
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
foreign import ccall "gtk_icon_theme_lookup_icon_for_scale" gtk_icon_theme_lookup_icon_for_scale ::
Ptr IconTheme ->
CString ->
Int32 ->
Int32 ->
CUInt ->
IO (Ptr Gtk.IconInfo.IconInfo)
iconThemeLookupIconForScale ::
(B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
a
-> T.Text
-> Int32
-> Int32
-> [Gtk.Flags.IconLookupFlags]
-> m (Maybe Gtk.IconInfo.IconInfo)
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
foreign import ccall "gtk_icon_theme_prepend_search_path" gtk_icon_theme_prepend_search_path ::
Ptr IconTheme ->
CString ->
IO ()
iconThemePrependSearchPath ::
(B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
a
-> [Char]
-> 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
foreign import ccall "gtk_icon_theme_rescan_if_needed" gtk_icon_theme_rescan_if_needed ::
Ptr IconTheme ->
IO CInt
iconThemeRescanIfNeeded ::
(B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
a
-> m Bool
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
foreign import ccall "gtk_icon_theme_set_custom_theme" gtk_icon_theme_set_custom_theme ::
Ptr IconTheme ->
CString ->
IO ()
iconThemeSetCustomTheme ::
(B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
a
-> Maybe (T.Text)
-> 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
foreign import ccall "gtk_icon_theme_set_screen" gtk_icon_theme_set_screen ::
Ptr IconTheme ->
Ptr Gdk.Screen.Screen ->
IO ()
iconThemeSetScreen ::
(B.CallStack.HasCallStack, MonadIO m, IsIconTheme a, Gdk.Screen.IsScreen b) =>
a
-> b
-> 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
foreign import ccall "gtk_icon_theme_set_search_path" gtk_icon_theme_set_search_path ::
Ptr IconTheme ->
Ptr CString ->
Int32 ->
IO ()
iconThemeSetSearchPath ::
(B.CallStack.HasCallStack, MonadIO m, IsIconTheme a) =>
a
-> [[Char]]
-> 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
foreign import ccall "gtk_icon_theme_add_builtin_icon" gtk_icon_theme_add_builtin_icon ::
CString ->
Int32 ->
Ptr GdkPixbuf.Pixbuf.Pixbuf ->
IO ()
{-# DEPRECATED iconThemeAddBuiltinIcon ["(Since version 3.14)","Use 'GI.Gtk.Objects.IconTheme.iconThemeAddResourcePath'"," to add application-specific icons to the icon theme."] #-}
iconThemeAddBuiltinIcon ::
(B.CallStack.HasCallStack, MonadIO m, GdkPixbuf.Pixbuf.IsPixbuf a) =>
T.Text
-> Int32
-> a
-> 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
foreign import ccall "gtk_icon_theme_get_default" gtk_icon_theme_get_default ::
IO (Ptr IconTheme)
iconThemeGetDefault ::
(B.CallStack.HasCallStack, MonadIO m) =>
m IconTheme
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
foreign import ccall "gtk_icon_theme_get_for_screen" gtk_icon_theme_get_for_screen ::
Ptr Gdk.Screen.Screen ->
IO (Ptr IconTheme)
iconThemeGetForScreen ::
(B.CallStack.HasCallStack, MonadIO m, Gdk.Screen.IsScreen a) =>
a
-> m IconTheme
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