{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Structs.IconSet
(
IconSet(..) ,
#if defined(ENABLE_OVERLOADING)
ResolveIconSetMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
IconSetAddSourceMethodInfo ,
#endif
iconSetAddSource ,
#if defined(ENABLE_OVERLOADING)
IconSetCopyMethodInfo ,
#endif
iconSetCopy ,
#if defined(ENABLE_OVERLOADING)
IconSetGetSizesMethodInfo ,
#endif
iconSetGetSizes ,
iconSetNew ,
iconSetNewFromPixbuf ,
#if defined(ENABLE_OVERLOADING)
IconSetRefMethodInfo ,
#endif
iconSetRef ,
#if defined(ENABLE_OVERLOADING)
IconSetRenderIconMethodInfo ,
#endif
iconSetRenderIcon ,
#if defined(ENABLE_OVERLOADING)
IconSetRenderIconPixbufMethodInfo ,
#endif
iconSetRenderIconPixbuf ,
#if defined(ENABLE_OVERLOADING)
IconSetRenderIconSurfaceMethodInfo ,
#endif
iconSetRenderIconSurface ,
#if defined(ENABLE_OVERLOADING)
IconSetUnrefMethodInfo ,
#endif
iconSetUnref ,
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GI.Cairo.Structs.Surface as Cairo.Surface
import qualified GI.Gdk.Objects.Window as Gdk.Window
import qualified GI.GdkPixbuf.Objects.Pixbuf as GdkPixbuf.Pixbuf
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Objects.Style as Gtk.Style
import {-# SOURCE #-} qualified GI.Gtk.Objects.StyleContext as Gtk.StyleContext
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget
import {-# SOURCE #-} qualified GI.Gtk.Structs.IconSource as Gtk.IconSource
newtype IconSet = IconSet (SP.ManagedPtr IconSet)
deriving (IconSet -> IconSet -> Bool
(IconSet -> IconSet -> Bool)
-> (IconSet -> IconSet -> Bool) -> Eq IconSet
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IconSet -> IconSet -> Bool
$c/= :: IconSet -> IconSet -> Bool
== :: IconSet -> IconSet -> Bool
$c== :: IconSet -> IconSet -> Bool
Eq)
instance SP.ManagedPtrNewtype IconSet where
toManagedPtr :: IconSet -> ManagedPtr IconSet
toManagedPtr (IconSet ManagedPtr IconSet
p) = ManagedPtr IconSet
p
foreign import ccall "gtk_icon_set_get_type" c_gtk_icon_set_get_type ::
IO GType
type instance O.ParentTypes IconSet = '[]
instance O.HasParentTypes IconSet
instance B.Types.TypedObject IconSet where
glibType :: IO GType
glibType = IO GType
c_gtk_icon_set_get_type
instance B.Types.GBoxed IconSet
instance B.GValue.IsGValue IconSet where
toGValue :: IconSet -> IO GValue
toGValue IconSet
o = do
GType
gtype <- IO GType
c_gtk_icon_set_get_type
IconSet -> (Ptr IconSet -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr IconSet
o (GType
-> (GValue -> Ptr IconSet -> IO ()) -> Ptr IconSet -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr IconSet -> IO ()
forall a. GValue -> Ptr a -> IO ()
B.GValue.set_boxed)
fromGValue :: GValue -> IO IconSet
fromGValue GValue
gv = do
Ptr IconSet
ptr <- GValue -> IO (Ptr IconSet)
forall b. GValue -> IO (Ptr b)
B.GValue.get_boxed GValue
gv :: IO (Ptr IconSet)
(ManagedPtr IconSet -> IconSet) -> Ptr IconSet -> IO IconSet
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr IconSet -> IconSet
IconSet Ptr IconSet
ptr
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList IconSet
type instance O.AttributeList IconSet = IconSetAttributeList
type IconSetAttributeList = ('[ ] :: [(Symbol, *)])
#endif
foreign import ccall "gtk_icon_set_new" gtk_icon_set_new ::
IO (Ptr IconSet)
{-# DEPRECATED iconSetNew ["(Since version 3.10)","Use t'GI.Gtk.Objects.IconTheme.IconTheme' instead."] #-}
iconSetNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
m IconSet
iconSetNew :: m IconSet
iconSetNew = IO IconSet -> m IconSet
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO IconSet -> m IconSet) -> IO IconSet -> m IconSet
forall a b. (a -> b) -> a -> b
$ do
Ptr IconSet
result <- IO (Ptr IconSet)
gtk_icon_set_new
Text -> Ptr IconSet -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iconSetNew" Ptr IconSet
result
IconSet
result' <- ((ManagedPtr IconSet -> IconSet) -> Ptr IconSet -> IO IconSet
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr IconSet -> IconSet
IconSet) Ptr IconSet
result
IconSet -> IO IconSet
forall (m :: * -> *) a. Monad m => a -> m a
return IconSet
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_icon_set_new_from_pixbuf" gtk_icon_set_new_from_pixbuf ::
Ptr GdkPixbuf.Pixbuf.Pixbuf ->
IO (Ptr IconSet)
{-# DEPRECATED iconSetNewFromPixbuf ["(Since version 3.10)","Use t'GI.Gtk.Objects.IconTheme.IconTheme' instead."] #-}
iconSetNewFromPixbuf ::
(B.CallStack.HasCallStack, MonadIO m, GdkPixbuf.Pixbuf.IsPixbuf a) =>
a
-> m IconSet
iconSetNewFromPixbuf :: a -> m IconSet
iconSetNewFromPixbuf a
pixbuf = IO IconSet -> m IconSet
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO IconSet -> m IconSet) -> IO IconSet -> m IconSet
forall a b. (a -> b) -> a -> b
$ do
Ptr Pixbuf
pixbuf' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pixbuf
Ptr IconSet
result <- Ptr Pixbuf -> IO (Ptr IconSet)
gtk_icon_set_new_from_pixbuf Ptr Pixbuf
pixbuf'
Text -> Ptr IconSet -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iconSetNewFromPixbuf" Ptr IconSet
result
IconSet
result' <- ((ManagedPtr IconSet -> IconSet) -> Ptr IconSet -> IO IconSet
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr IconSet -> IconSet
IconSet) Ptr IconSet
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pixbuf
IconSet -> IO IconSet
forall (m :: * -> *) a. Monad m => a -> m a
return IconSet
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_icon_set_add_source" gtk_icon_set_add_source ::
Ptr IconSet ->
Ptr Gtk.IconSource.IconSource ->
IO ()
{-# DEPRECATED iconSetAddSource ["(Since version 3.10)","Use t'GI.Gtk.Objects.IconTheme.IconTheme' instead."] #-}
iconSetAddSource ::
(B.CallStack.HasCallStack, MonadIO m) =>
IconSet
-> Gtk.IconSource.IconSource
-> m ()
iconSetAddSource :: IconSet -> IconSource -> m ()
iconSetAddSource IconSet
iconSet IconSource
source = 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 IconSet
iconSet' <- IconSet -> IO (Ptr IconSet)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr IconSet
iconSet
Ptr IconSource
source' <- IconSource -> IO (Ptr IconSource)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr IconSource
source
Ptr IconSet -> Ptr IconSource -> IO ()
gtk_icon_set_add_source Ptr IconSet
iconSet' Ptr IconSource
source'
IconSet -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr IconSet
iconSet
IconSource -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr IconSource
source
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data IconSetAddSourceMethodInfo
instance (signature ~ (Gtk.IconSource.IconSource -> m ()), MonadIO m) => O.MethodInfo IconSetAddSourceMethodInfo IconSet signature where
overloadedMethod = iconSetAddSource
#endif
foreign import ccall "gtk_icon_set_copy" gtk_icon_set_copy ::
Ptr IconSet ->
IO (Ptr IconSet)
{-# DEPRECATED iconSetCopy ["(Since version 3.10)","Use t'GI.Gtk.Objects.IconTheme.IconTheme' instead."] #-}
iconSetCopy ::
(B.CallStack.HasCallStack, MonadIO m) =>
IconSet
-> m IconSet
iconSetCopy :: IconSet -> m IconSet
iconSetCopy IconSet
iconSet = IO IconSet -> m IconSet
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO IconSet -> m IconSet) -> IO IconSet -> m IconSet
forall a b. (a -> b) -> a -> b
$ do
Ptr IconSet
iconSet' <- IconSet -> IO (Ptr IconSet)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr IconSet
iconSet
Ptr IconSet
result <- Ptr IconSet -> IO (Ptr IconSet)
gtk_icon_set_copy Ptr IconSet
iconSet'
Text -> Ptr IconSet -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iconSetCopy" Ptr IconSet
result
IconSet
result' <- ((ManagedPtr IconSet -> IconSet) -> Ptr IconSet -> IO IconSet
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr IconSet -> IconSet
IconSet) Ptr IconSet
result
IconSet -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr IconSet
iconSet
IconSet -> IO IconSet
forall (m :: * -> *) a. Monad m => a -> m a
return IconSet
result'
#if defined(ENABLE_OVERLOADING)
data IconSetCopyMethodInfo
instance (signature ~ (m IconSet), MonadIO m) => O.MethodInfo IconSetCopyMethodInfo IconSet signature where
overloadedMethod = iconSetCopy
#endif
foreign import ccall "gtk_icon_set_get_sizes" gtk_icon_set_get_sizes ::
Ptr IconSet ->
Ptr (Ptr Int32) ->
Ptr Int32 ->
IO ()
{-# DEPRECATED iconSetGetSizes ["(Since version 3.10)","Use t'GI.Gtk.Objects.IconTheme.IconTheme' instead."] #-}
iconSetGetSizes ::
(B.CallStack.HasCallStack, MonadIO m) =>
IconSet
-> m ([Int32])
iconSetGetSizes :: IconSet -> m [Int32]
iconSetGetSizes IconSet
iconSet = 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 IconSet
iconSet' <- IconSet -> IO (Ptr IconSet)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr IconSet
iconSet
Ptr (Ptr Int32)
sizes <- IO (Ptr (Ptr Int32))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (Ptr Int32))
Ptr Int32
nSizes <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
Ptr IconSet -> Ptr (Ptr Int32) -> Ptr Int32 -> IO ()
gtk_icon_set_get_sizes Ptr IconSet
iconSet' Ptr (Ptr Int32)
sizes Ptr Int32
nSizes
Int32
nSizes' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
nSizes
Ptr Int32
sizes' <- Ptr (Ptr Int32) -> IO (Ptr Int32)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr Int32)
sizes
[Int32]
sizes'' <- (Int32 -> Ptr Int32 -> IO [Int32]
forall a b. (Integral a, Storable b) => a -> Ptr b -> IO [b]
unpackStorableArrayWithLength Int32
nSizes') Ptr Int32
sizes'
Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
sizes'
IconSet -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr IconSet
iconSet
Ptr (Ptr Int32) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr Int32)
sizes
Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
nSizes
[Int32] -> IO [Int32]
forall (m :: * -> *) a. Monad m => a -> m a
return [Int32]
sizes''
#if defined(ENABLE_OVERLOADING)
data IconSetGetSizesMethodInfo
instance (signature ~ (m ([Int32])), MonadIO m) => O.MethodInfo IconSetGetSizesMethodInfo IconSet signature where
overloadedMethod = iconSetGetSizes
#endif
foreign import ccall "gtk_icon_set_ref" gtk_icon_set_ref ::
Ptr IconSet ->
IO (Ptr IconSet)
{-# DEPRECATED iconSetRef ["(Since version 3.10)","Use t'GI.Gtk.Objects.IconTheme.IconTheme' instead."] #-}
iconSetRef ::
(B.CallStack.HasCallStack, MonadIO m) =>
IconSet
-> m IconSet
iconSetRef :: IconSet -> m IconSet
iconSetRef IconSet
iconSet = IO IconSet -> m IconSet
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO IconSet -> m IconSet) -> IO IconSet -> m IconSet
forall a b. (a -> b) -> a -> b
$ do
Ptr IconSet
iconSet' <- IconSet -> IO (Ptr IconSet)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr IconSet
iconSet
Ptr IconSet
result <- Ptr IconSet -> IO (Ptr IconSet)
gtk_icon_set_ref Ptr IconSet
iconSet'
Text -> Ptr IconSet -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iconSetRef" Ptr IconSet
result
IconSet
result' <- ((ManagedPtr IconSet -> IconSet) -> Ptr IconSet -> IO IconSet
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr IconSet -> IconSet
IconSet) Ptr IconSet
result
IconSet -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr IconSet
iconSet
IconSet -> IO IconSet
forall (m :: * -> *) a. Monad m => a -> m a
return IconSet
result'
#if defined(ENABLE_OVERLOADING)
data IconSetRefMethodInfo
instance (signature ~ (m IconSet), MonadIO m) => O.MethodInfo IconSetRefMethodInfo IconSet signature where
overloadedMethod = iconSetRef
#endif
foreign import ccall "gtk_icon_set_render_icon" gtk_icon_set_render_icon ::
Ptr IconSet ->
Ptr Gtk.Style.Style ->
CUInt ->
CUInt ->
Int32 ->
Ptr Gtk.Widget.Widget ->
CString ->
IO (Ptr GdkPixbuf.Pixbuf.Pixbuf)
{-# DEPRECATED iconSetRenderIcon ["(Since version 3.0)","Use 'GI.Gtk.Structs.IconSet.iconSetRenderIconPixbuf' instead"] #-}
iconSetRenderIcon ::
(B.CallStack.HasCallStack, MonadIO m, Gtk.Style.IsStyle a, Gtk.Widget.IsWidget b) =>
IconSet
-> Maybe (a)
-> Gtk.Enums.TextDirection
-> Gtk.Enums.StateType
-> Int32
-> Maybe (b)
-> Maybe (T.Text)
-> m GdkPixbuf.Pixbuf.Pixbuf
iconSetRenderIcon :: IconSet
-> Maybe a
-> TextDirection
-> StateType
-> Int32
-> Maybe b
-> Maybe Text
-> m Pixbuf
iconSetRenderIcon IconSet
iconSet Maybe a
style TextDirection
direction StateType
state Int32
size Maybe b
widget Maybe Text
detail = IO Pixbuf -> m Pixbuf
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Pixbuf -> m Pixbuf) -> IO Pixbuf -> m Pixbuf
forall a b. (a -> b) -> a -> b
$ do
Ptr IconSet
iconSet' <- IconSet -> IO (Ptr IconSet)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr IconSet
iconSet
Ptr Style
maybeStyle <- case Maybe a
style of
Maybe a
Nothing -> Ptr Style -> IO (Ptr Style)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Style
forall a. Ptr a
nullPtr
Just a
jStyle -> do
Ptr Style
jStyle' <- a -> IO (Ptr Style)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jStyle
Ptr Style -> IO (Ptr Style)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Style
jStyle'
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 state' :: CUInt
state' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (StateType -> Int) -> StateType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StateType -> Int
forall a. Enum a => a -> Int
fromEnum) StateType
state
Ptr Widget
maybeWidget <- case Maybe b
widget of
Maybe b
Nothing -> Ptr Widget -> IO (Ptr Widget)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
forall a. Ptr a
nullPtr
Just b
jWidget -> do
Ptr Widget
jWidget' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jWidget
Ptr Widget -> IO (Ptr Widget)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
jWidget'
Ptr CChar
maybeDetail <- case Maybe Text
detail of
Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
Just Text
jDetail -> do
Ptr CChar
jDetail' <- Text -> IO (Ptr CChar)
textToCString Text
jDetail
Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jDetail'
Ptr Pixbuf
result <- Ptr IconSet
-> Ptr Style
-> CUInt
-> CUInt
-> Int32
-> Ptr Widget
-> Ptr CChar
-> IO (Ptr Pixbuf)
gtk_icon_set_render_icon Ptr IconSet
iconSet' Ptr Style
maybeStyle CUInt
direction' CUInt
state' Int32
size Ptr Widget
maybeWidget Ptr CChar
maybeDetail
Text -> Ptr Pixbuf -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iconSetRenderIcon" Ptr Pixbuf
result
Pixbuf
result' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Pixbuf -> Pixbuf
GdkPixbuf.Pixbuf.Pixbuf) Ptr Pixbuf
result
IconSet -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr IconSet
iconSet
Maybe a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
style a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
widget b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeDetail
Pixbuf -> IO Pixbuf
forall (m :: * -> *) a. Monad m => a -> m a
return Pixbuf
result'
#if defined(ENABLE_OVERLOADING)
data IconSetRenderIconMethodInfo
instance (signature ~ (Maybe (a) -> Gtk.Enums.TextDirection -> Gtk.Enums.StateType -> Int32 -> Maybe (b) -> Maybe (T.Text) -> m GdkPixbuf.Pixbuf.Pixbuf), MonadIO m, Gtk.Style.IsStyle a, Gtk.Widget.IsWidget b) => O.MethodInfo IconSetRenderIconMethodInfo IconSet signature where
overloadedMethod = iconSetRenderIcon
#endif
foreign import ccall "gtk_icon_set_render_icon_pixbuf" gtk_icon_set_render_icon_pixbuf ::
Ptr IconSet ->
Ptr Gtk.StyleContext.StyleContext ->
Int32 ->
IO (Ptr GdkPixbuf.Pixbuf.Pixbuf)
{-# DEPRECATED iconSetRenderIconPixbuf ["(Since version 3.10)","Use t'GI.Gtk.Objects.IconTheme.IconTheme' instead."] #-}
iconSetRenderIconPixbuf ::
(B.CallStack.HasCallStack, MonadIO m, Gtk.StyleContext.IsStyleContext a) =>
IconSet
-> a
-> Int32
-> m GdkPixbuf.Pixbuf.Pixbuf
iconSetRenderIconPixbuf :: IconSet -> a -> Int32 -> m Pixbuf
iconSetRenderIconPixbuf IconSet
iconSet a
context Int32
size = IO Pixbuf -> m Pixbuf
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Pixbuf -> m Pixbuf) -> IO Pixbuf -> m Pixbuf
forall a b. (a -> b) -> a -> b
$ do
Ptr IconSet
iconSet' <- IconSet -> IO (Ptr IconSet)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr IconSet
iconSet
Ptr StyleContext
context' <- a -> IO (Ptr StyleContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
Ptr Pixbuf
result <- Ptr IconSet -> Ptr StyleContext -> Int32 -> IO (Ptr Pixbuf)
gtk_icon_set_render_icon_pixbuf Ptr IconSet
iconSet' Ptr StyleContext
context' Int32
size
Text -> Ptr Pixbuf -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iconSetRenderIconPixbuf" Ptr Pixbuf
result
Pixbuf
result' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Pixbuf -> Pixbuf
GdkPixbuf.Pixbuf.Pixbuf) Ptr Pixbuf
result
IconSet -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr IconSet
iconSet
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
Pixbuf -> IO Pixbuf
forall (m :: * -> *) a. Monad m => a -> m a
return Pixbuf
result'
#if defined(ENABLE_OVERLOADING)
data IconSetRenderIconPixbufMethodInfo
instance (signature ~ (a -> Int32 -> m GdkPixbuf.Pixbuf.Pixbuf), MonadIO m, Gtk.StyleContext.IsStyleContext a) => O.MethodInfo IconSetRenderIconPixbufMethodInfo IconSet signature where
overloadedMethod = iconSetRenderIconPixbuf
#endif
foreign import ccall "gtk_icon_set_render_icon_surface" gtk_icon_set_render_icon_surface ::
Ptr IconSet ->
Ptr Gtk.StyleContext.StyleContext ->
Int32 ->
Int32 ->
Ptr Gdk.Window.Window ->
IO (Ptr Cairo.Surface.Surface)
{-# DEPRECATED iconSetRenderIconSurface ["(Since version 3.10)","Use t'GI.Gtk.Objects.IconTheme.IconTheme' instead."] #-}
iconSetRenderIconSurface ::
(B.CallStack.HasCallStack, MonadIO m, Gtk.StyleContext.IsStyleContext a, Gdk.Window.IsWindow b) =>
IconSet
-> a
-> Int32
-> Int32
-> Maybe (b)
-> m Cairo.Surface.Surface
iconSetRenderIconSurface :: IconSet -> a -> Int32 -> Int32 -> Maybe b -> m Surface
iconSetRenderIconSurface IconSet
iconSet a
context Int32
size Int32
scale Maybe b
forWindow = IO Surface -> m Surface
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Surface -> m Surface) -> IO Surface -> m Surface
forall a b. (a -> b) -> a -> b
$ do
Ptr IconSet
iconSet' <- IconSet -> IO (Ptr IconSet)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr IconSet
iconSet
Ptr StyleContext
context' <- a -> IO (Ptr StyleContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
Ptr Window
maybeForWindow <- case Maybe b
forWindow of
Maybe b
Nothing -> Ptr Window -> IO (Ptr Window)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Window
forall a. Ptr a
nullPtr
Just b
jForWindow -> do
Ptr Window
jForWindow' <- b -> IO (Ptr Window)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jForWindow
Ptr Window -> IO (Ptr Window)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Window
jForWindow'
Ptr Surface
result <- Ptr IconSet
-> Ptr StyleContext
-> Int32
-> Int32
-> Ptr Window
-> IO (Ptr Surface)
gtk_icon_set_render_icon_surface Ptr IconSet
iconSet' Ptr StyleContext
context' Int32
size Int32
scale Ptr Window
maybeForWindow
Text -> Ptr Surface -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iconSetRenderIconSurface" Ptr Surface
result
Surface
result' <- ((ManagedPtr Surface -> Surface) -> Ptr Surface -> IO Surface
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Surface -> Surface
Cairo.Surface.Surface) Ptr Surface
result
IconSet -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr IconSet
iconSet
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
forWindow b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Surface -> IO Surface
forall (m :: * -> *) a. Monad m => a -> m a
return Surface
result'
#if defined(ENABLE_OVERLOADING)
data IconSetRenderIconSurfaceMethodInfo
instance (signature ~ (a -> Int32 -> Int32 -> Maybe (b) -> m Cairo.Surface.Surface), MonadIO m, Gtk.StyleContext.IsStyleContext a, Gdk.Window.IsWindow b) => O.MethodInfo IconSetRenderIconSurfaceMethodInfo IconSet signature where
overloadedMethod = iconSetRenderIconSurface
#endif
foreign import ccall "gtk_icon_set_unref" gtk_icon_set_unref ::
Ptr IconSet ->
IO ()
{-# DEPRECATED iconSetUnref ["(Since version 3.10)","Use t'GI.Gtk.Objects.IconTheme.IconTheme' instead."] #-}
iconSetUnref ::
(B.CallStack.HasCallStack, MonadIO m) =>
IconSet
-> m ()
iconSetUnref :: IconSet -> m ()
iconSetUnref IconSet
iconSet = 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 IconSet
iconSet' <- IconSet -> IO (Ptr IconSet)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr IconSet
iconSet
Ptr IconSet -> IO ()
gtk_icon_set_unref Ptr IconSet
iconSet'
IconSet -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr IconSet
iconSet
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data IconSetUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo IconSetUnrefMethodInfo IconSet signature where
overloadedMethod = iconSetUnref
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveIconSetMethod (t :: Symbol) (o :: *) :: * where
ResolveIconSetMethod "addSource" o = IconSetAddSourceMethodInfo
ResolveIconSetMethod "copy" o = IconSetCopyMethodInfo
ResolveIconSetMethod "ref" o = IconSetRefMethodInfo
ResolveIconSetMethod "renderIcon" o = IconSetRenderIconMethodInfo
ResolveIconSetMethod "renderIconPixbuf" o = IconSetRenderIconPixbufMethodInfo
ResolveIconSetMethod "renderIconSurface" o = IconSetRenderIconSurfaceMethodInfo
ResolveIconSetMethod "unref" o = IconSetUnrefMethodInfo
ResolveIconSetMethod "getSizes" o = IconSetGetSizesMethodInfo
ResolveIconSetMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveIconSetMethod t IconSet, O.MethodInfo info IconSet p) => OL.IsLabel t (IconSet -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif