{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Objects.NumerableIcon
(
NumerableIcon(..) ,
IsNumerableIcon ,
toNumerableIcon ,
#if defined(ENABLE_OVERLOADING)
ResolveNumerableIconMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
NumerableIconGetBackgroundGiconMethodInfo,
#endif
numerableIconGetBackgroundGicon ,
#if defined(ENABLE_OVERLOADING)
NumerableIconGetBackgroundIconNameMethodInfo,
#endif
numerableIconGetBackgroundIconName ,
#if defined(ENABLE_OVERLOADING)
NumerableIconGetCountMethodInfo ,
#endif
numerableIconGetCount ,
#if defined(ENABLE_OVERLOADING)
NumerableIconGetLabelMethodInfo ,
#endif
numerableIconGetLabel ,
#if defined(ENABLE_OVERLOADING)
NumerableIconGetStyleContextMethodInfo ,
#endif
numerableIconGetStyleContext ,
numerableIconNew ,
numerableIconNewWithStyleContext ,
#if defined(ENABLE_OVERLOADING)
NumerableIconSetBackgroundGiconMethodInfo,
#endif
numerableIconSetBackgroundGicon ,
#if defined(ENABLE_OVERLOADING)
NumerableIconSetBackgroundIconNameMethodInfo,
#endif
numerableIconSetBackgroundIconName ,
#if defined(ENABLE_OVERLOADING)
NumerableIconSetCountMethodInfo ,
#endif
numerableIconSetCount ,
#if defined(ENABLE_OVERLOADING)
NumerableIconSetLabelMethodInfo ,
#endif
numerableIconSetLabel ,
#if defined(ENABLE_OVERLOADING)
NumerableIconSetStyleContextMethodInfo ,
#endif
numerableIconSetStyleContext ,
#if defined(ENABLE_OVERLOADING)
NumerableIconBackgroundIconPropertyInfo ,
#endif
clearNumerableIconBackgroundIcon ,
constructNumerableIconBackgroundIcon ,
getNumerableIconBackgroundIcon ,
#if defined(ENABLE_OVERLOADING)
numerableIconBackgroundIcon ,
#endif
setNumerableIconBackgroundIcon ,
#if defined(ENABLE_OVERLOADING)
NumerableIconBackgroundIconNamePropertyInfo,
#endif
clearNumerableIconBackgroundIconName ,
constructNumerableIconBackgroundIconName,
getNumerableIconBackgroundIconName ,
#if defined(ENABLE_OVERLOADING)
numerableIconBackgroundIconName ,
#endif
setNumerableIconBackgroundIconName ,
#if defined(ENABLE_OVERLOADING)
NumerableIconCountPropertyInfo ,
#endif
constructNumerableIconCount ,
getNumerableIconCount ,
#if defined(ENABLE_OVERLOADING)
numerableIconCount ,
#endif
setNumerableIconCount ,
#if defined(ENABLE_OVERLOADING)
NumerableIconLabelPropertyInfo ,
#endif
clearNumerableIconLabel ,
constructNumerableIconLabel ,
getNumerableIconLabel ,
#if defined(ENABLE_OVERLOADING)
numerableIconLabel ,
#endif
setNumerableIconLabel ,
#if defined(ENABLE_OVERLOADING)
NumerableIconStyleContextPropertyInfo ,
#endif
constructNumerableIconStyleContext ,
getNumerableIconStyleContext ,
#if defined(ENABLE_OVERLOADING)
numerableIconStyleContext ,
#endif
setNumerableIconStyleContext ,
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Interfaces.Icon as Gio.Icon
import qualified GI.Gio.Objects.EmblemedIcon as Gio.EmblemedIcon
import {-# SOURCE #-} qualified GI.Gtk.Objects.StyleContext as Gtk.StyleContext
newtype NumerableIcon = NumerableIcon (SP.ManagedPtr NumerableIcon)
deriving (NumerableIcon -> NumerableIcon -> Bool
(NumerableIcon -> NumerableIcon -> Bool)
-> (NumerableIcon -> NumerableIcon -> Bool) -> Eq NumerableIcon
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NumerableIcon -> NumerableIcon -> Bool
== :: NumerableIcon -> NumerableIcon -> Bool
$c/= :: NumerableIcon -> NumerableIcon -> Bool
/= :: NumerableIcon -> NumerableIcon -> Bool
Eq)
instance SP.ManagedPtrNewtype NumerableIcon where
toManagedPtr :: NumerableIcon -> ManagedPtr NumerableIcon
toManagedPtr (NumerableIcon ManagedPtr NumerableIcon
p) = ManagedPtr NumerableIcon
p
foreign import ccall "gtk_numerable_icon_get_type"
c_gtk_numerable_icon_get_type :: IO B.Types.GType
instance B.Types.TypedObject NumerableIcon where
glibType :: IO GType
glibType = IO GType
c_gtk_numerable_icon_get_type
instance B.Types.GObject NumerableIcon
class (SP.GObject o, O.IsDescendantOf NumerableIcon o) => IsNumerableIcon o
instance (SP.GObject o, O.IsDescendantOf NumerableIcon o) => IsNumerableIcon o
instance O.HasParentTypes NumerableIcon
type instance O.ParentTypes NumerableIcon = '[Gio.EmblemedIcon.EmblemedIcon, GObject.Object.Object, Gio.Icon.Icon]
toNumerableIcon :: (MIO.MonadIO m, IsNumerableIcon o) => o -> m NumerableIcon
toNumerableIcon :: forall (m :: * -> *) o.
(MonadIO m, IsNumerableIcon o) =>
o -> m NumerableIcon
toNumerableIcon = IO NumerableIcon -> m NumerableIcon
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO NumerableIcon -> m NumerableIcon)
-> (o -> IO NumerableIcon) -> o -> m NumerableIcon
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr NumerableIcon -> NumerableIcon)
-> o -> IO NumerableIcon
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr NumerableIcon -> NumerableIcon
NumerableIcon
instance B.GValue.IsGValue (Maybe NumerableIcon) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_numerable_icon_get_type
gvalueSet_ :: Ptr GValue -> Maybe NumerableIcon -> IO ()
gvalueSet_ Ptr GValue
gv Maybe NumerableIcon
P.Nothing = Ptr GValue -> Ptr NumerableIcon -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr NumerableIcon
forall a. Ptr a
FP.nullPtr :: FP.Ptr NumerableIcon)
gvalueSet_ Ptr GValue
gv (P.Just NumerableIcon
obj) = NumerableIcon -> (Ptr NumerableIcon -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr NumerableIcon
obj (Ptr GValue -> Ptr NumerableIcon -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe NumerableIcon)
gvalueGet_ Ptr GValue
gv = do
Ptr NumerableIcon
ptr <- Ptr GValue -> IO (Ptr NumerableIcon)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr NumerableIcon)
if Ptr NumerableIcon
ptr Ptr NumerableIcon -> Ptr NumerableIcon -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr NumerableIcon
forall a. Ptr a
FP.nullPtr
then NumerableIcon -> Maybe NumerableIcon
forall a. a -> Maybe a
P.Just (NumerableIcon -> Maybe NumerableIcon)
-> IO NumerableIcon -> IO (Maybe NumerableIcon)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr NumerableIcon -> NumerableIcon)
-> Ptr NumerableIcon -> IO NumerableIcon
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr NumerableIcon -> NumerableIcon
NumerableIcon Ptr NumerableIcon
ptr
else Maybe NumerableIcon -> IO (Maybe NumerableIcon)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe NumerableIcon
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveNumerableIconMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveNumerableIconMethod "addEmblem" o = Gio.EmblemedIcon.EmblemedIconAddEmblemMethodInfo
ResolveNumerableIconMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveNumerableIconMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveNumerableIconMethod "clearEmblems" o = Gio.EmblemedIcon.EmblemedIconClearEmblemsMethodInfo
ResolveNumerableIconMethod "equal" o = Gio.Icon.IconEqualMethodInfo
ResolveNumerableIconMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveNumerableIconMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveNumerableIconMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveNumerableIconMethod "hash" o = Gio.Icon.IconHashMethodInfo
ResolveNumerableIconMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveNumerableIconMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveNumerableIconMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveNumerableIconMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveNumerableIconMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveNumerableIconMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveNumerableIconMethod "serialize" o = Gio.Icon.IconSerializeMethodInfo
ResolveNumerableIconMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveNumerableIconMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveNumerableIconMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveNumerableIconMethod "toString" o = Gio.Icon.IconToStringMethodInfo
ResolveNumerableIconMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveNumerableIconMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveNumerableIconMethod "getBackgroundGicon" o = NumerableIconGetBackgroundGiconMethodInfo
ResolveNumerableIconMethod "getBackgroundIconName" o = NumerableIconGetBackgroundIconNameMethodInfo
ResolveNumerableIconMethod "getCount" o = NumerableIconGetCountMethodInfo
ResolveNumerableIconMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveNumerableIconMethod "getEmblems" o = Gio.EmblemedIcon.EmblemedIconGetEmblemsMethodInfo
ResolveNumerableIconMethod "getIcon" o = Gio.EmblemedIcon.EmblemedIconGetIconMethodInfo
ResolveNumerableIconMethod "getLabel" o = NumerableIconGetLabelMethodInfo
ResolveNumerableIconMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveNumerableIconMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveNumerableIconMethod "getStyleContext" o = NumerableIconGetStyleContextMethodInfo
ResolveNumerableIconMethod "setBackgroundGicon" o = NumerableIconSetBackgroundGiconMethodInfo
ResolveNumerableIconMethod "setBackgroundIconName" o = NumerableIconSetBackgroundIconNameMethodInfo
ResolveNumerableIconMethod "setCount" o = NumerableIconSetCountMethodInfo
ResolveNumerableIconMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveNumerableIconMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveNumerableIconMethod "setLabel" o = NumerableIconSetLabelMethodInfo
ResolveNumerableIconMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveNumerableIconMethod "setStyleContext" o = NumerableIconSetStyleContextMethodInfo
ResolveNumerableIconMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveNumerableIconMethod t NumerableIcon, O.OverloadedMethod info NumerableIcon p) => OL.IsLabel t (NumerableIcon -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveNumerableIconMethod t NumerableIcon, O.OverloadedMethod info NumerableIcon p, R.HasField t NumerableIcon p) => R.HasField t NumerableIcon p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveNumerableIconMethod t NumerableIcon, O.OverloadedMethodInfo info NumerableIcon) => OL.IsLabel t (O.MethodProxy info NumerableIcon) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
getNumerableIconBackgroundIcon :: (MonadIO m, IsNumerableIcon o) => o -> m (Maybe Gio.Icon.Icon)
getNumerableIconBackgroundIcon :: forall (m :: * -> *) o.
(MonadIO m, IsNumerableIcon o) =>
o -> m (Maybe Icon)
getNumerableIconBackgroundIcon o
obj = IO (Maybe Icon) -> m (Maybe Icon)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Icon) -> m (Maybe Icon))
-> IO (Maybe Icon) -> m (Maybe Icon)
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr Icon -> Icon) -> IO (Maybe Icon)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"background-icon" ManagedPtr Icon -> Icon
Gio.Icon.Icon
setNumerableIconBackgroundIcon :: (MonadIO m, IsNumerableIcon o, Gio.Icon.IsIcon a) => o -> a -> m ()
setNumerableIconBackgroundIcon :: forall (m :: * -> *) o a.
(MonadIO m, IsNumerableIcon o, IsIcon a) =>
o -> a -> m ()
setNumerableIconBackgroundIcon o
obj a
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"background-icon" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructNumerableIconBackgroundIcon :: (IsNumerableIcon o, MIO.MonadIO m, Gio.Icon.IsIcon a) => a -> m (GValueConstruct o)
constructNumerableIconBackgroundIcon :: forall o (m :: * -> *) a.
(IsNumerableIcon o, MonadIO m, IsIcon a) =>
a -> m (GValueConstruct o)
constructNumerableIconBackgroundIcon a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"background-icon" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
clearNumerableIconBackgroundIcon :: (MonadIO m, IsNumerableIcon o) => o -> m ()
clearNumerableIconBackgroundIcon :: forall (m :: * -> *) o. (MonadIO m, IsNumerableIcon o) => o -> m ()
clearNumerableIconBackgroundIcon o
obj = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Icon -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"background-icon" (Maybe Icon
forall a. Maybe a
Nothing :: Maybe Gio.Icon.Icon)
#if defined(ENABLE_OVERLOADING)
data NumerableIconBackgroundIconPropertyInfo
instance AttrInfo NumerableIconBackgroundIconPropertyInfo where
type AttrAllowedOps NumerableIconBackgroundIconPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint NumerableIconBackgroundIconPropertyInfo = IsNumerableIcon
type AttrSetTypeConstraint NumerableIconBackgroundIconPropertyInfo = Gio.Icon.IsIcon
type AttrTransferTypeConstraint NumerableIconBackgroundIconPropertyInfo = Gio.Icon.IsIcon
type AttrTransferType NumerableIconBackgroundIconPropertyInfo = Gio.Icon.Icon
type AttrGetType NumerableIconBackgroundIconPropertyInfo = (Maybe Gio.Icon.Icon)
type AttrLabel NumerableIconBackgroundIconPropertyInfo = "background-icon"
type AttrOrigin NumerableIconBackgroundIconPropertyInfo = NumerableIcon
attrGet = getNumerableIconBackgroundIcon
attrSet = setNumerableIconBackgroundIcon
attrTransfer _ v = do
unsafeCastTo Gio.Icon.Icon v
attrConstruct = constructNumerableIconBackgroundIcon
attrClear = clearNumerableIconBackgroundIcon
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.NumerableIcon.backgroundIcon"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-NumerableIcon.html#g:attr:backgroundIcon"
})
#endif
getNumerableIconBackgroundIconName :: (MonadIO m, IsNumerableIcon o) => o -> m (Maybe T.Text)
getNumerableIconBackgroundIconName :: forall (m :: * -> *) o.
(MonadIO m, IsNumerableIcon o) =>
o -> m (Maybe Text)
getNumerableIconBackgroundIconName o
obj = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"background-icon-name"
setNumerableIconBackgroundIconName :: (MonadIO m, IsNumerableIcon o) => o -> T.Text -> m ()
setNumerableIconBackgroundIconName :: forall (m :: * -> *) o.
(MonadIO m, IsNumerableIcon o) =>
o -> Text -> m ()
setNumerableIconBackgroundIconName o
obj Text
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"background-icon-name" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructNumerableIconBackgroundIconName :: (IsNumerableIcon o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructNumerableIconBackgroundIconName :: forall o (m :: * -> *).
(IsNumerableIcon o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructNumerableIconBackgroundIconName Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"background-icon-name" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
clearNumerableIconBackgroundIconName :: (MonadIO m, IsNumerableIcon o) => o -> m ()
clearNumerableIconBackgroundIconName :: forall (m :: * -> *) o. (MonadIO m, IsNumerableIcon o) => o -> m ()
clearNumerableIconBackgroundIconName o
obj = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"background-icon-name" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)
#if defined(ENABLE_OVERLOADING)
data NumerableIconBackgroundIconNamePropertyInfo
instance AttrInfo NumerableIconBackgroundIconNamePropertyInfo where
type AttrAllowedOps NumerableIconBackgroundIconNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint NumerableIconBackgroundIconNamePropertyInfo = IsNumerableIcon
type AttrSetTypeConstraint NumerableIconBackgroundIconNamePropertyInfo = (~) T.Text
type AttrTransferTypeConstraint NumerableIconBackgroundIconNamePropertyInfo = (~) T.Text
type AttrTransferType NumerableIconBackgroundIconNamePropertyInfo = T.Text
type AttrGetType NumerableIconBackgroundIconNamePropertyInfo = (Maybe T.Text)
type AttrLabel NumerableIconBackgroundIconNamePropertyInfo = "background-icon-name"
type AttrOrigin NumerableIconBackgroundIconNamePropertyInfo = NumerableIcon
attrGet = getNumerableIconBackgroundIconName
attrSet = setNumerableIconBackgroundIconName
attrTransfer _ v = do
return v
attrConstruct = constructNumerableIconBackgroundIconName
attrClear = clearNumerableIconBackgroundIconName
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.NumerableIcon.backgroundIconName"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-NumerableIcon.html#g:attr:backgroundIconName"
})
#endif
getNumerableIconCount :: (MonadIO m, IsNumerableIcon o) => o -> m Int32
getNumerableIconCount :: forall (m :: * -> *) o.
(MonadIO m, IsNumerableIcon o) =>
o -> m Int32
getNumerableIconCount o
obj = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"count"
setNumerableIconCount :: (MonadIO m, IsNumerableIcon o) => o -> Int32 -> m ()
setNumerableIconCount :: forall (m :: * -> *) o.
(MonadIO m, IsNumerableIcon o) =>
o -> Int32 -> m ()
setNumerableIconCount o
obj Int32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"count" Int32
val
constructNumerableIconCount :: (IsNumerableIcon o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructNumerableIconCount :: forall o (m :: * -> *).
(IsNumerableIcon o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructNumerableIconCount Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"count" Int32
val
#if defined(ENABLE_OVERLOADING)
data NumerableIconCountPropertyInfo
instance AttrInfo NumerableIconCountPropertyInfo where
type AttrAllowedOps NumerableIconCountPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint NumerableIconCountPropertyInfo = IsNumerableIcon
type AttrSetTypeConstraint NumerableIconCountPropertyInfo = (~) Int32
type AttrTransferTypeConstraint NumerableIconCountPropertyInfo = (~) Int32
type AttrTransferType NumerableIconCountPropertyInfo = Int32
type AttrGetType NumerableIconCountPropertyInfo = Int32
type AttrLabel NumerableIconCountPropertyInfo = "count"
type AttrOrigin NumerableIconCountPropertyInfo = NumerableIcon
attrGet = getNumerableIconCount
attrSet = setNumerableIconCount
attrTransfer _ v = do
return v
attrConstruct = constructNumerableIconCount
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.NumerableIcon.count"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-NumerableIcon.html#g:attr:count"
})
#endif
getNumerableIconLabel :: (MonadIO m, IsNumerableIcon o) => o -> m (Maybe T.Text)
getNumerableIconLabel :: forall (m :: * -> *) o.
(MonadIO m, IsNumerableIcon o) =>
o -> m (Maybe Text)
getNumerableIconLabel o
obj = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"label"
setNumerableIconLabel :: (MonadIO m, IsNumerableIcon o) => o -> T.Text -> m ()
setNumerableIconLabel :: forall (m :: * -> *) o.
(MonadIO m, IsNumerableIcon o) =>
o -> Text -> m ()
setNumerableIconLabel o
obj Text
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"label" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructNumerableIconLabel :: (IsNumerableIcon o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructNumerableIconLabel :: forall o (m :: * -> *).
(IsNumerableIcon o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructNumerableIconLabel Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"label" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
clearNumerableIconLabel :: (MonadIO m, IsNumerableIcon o) => o -> m ()
clearNumerableIconLabel :: forall (m :: * -> *) o. (MonadIO m, IsNumerableIcon o) => o -> m ()
clearNumerableIconLabel o
obj = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"label" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)
#if defined(ENABLE_OVERLOADING)
data NumerableIconLabelPropertyInfo
instance AttrInfo NumerableIconLabelPropertyInfo where
type AttrAllowedOps NumerableIconLabelPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint NumerableIconLabelPropertyInfo = IsNumerableIcon
type AttrSetTypeConstraint NumerableIconLabelPropertyInfo = (~) T.Text
type AttrTransferTypeConstraint NumerableIconLabelPropertyInfo = (~) T.Text
type AttrTransferType NumerableIconLabelPropertyInfo = T.Text
type AttrGetType NumerableIconLabelPropertyInfo = (Maybe T.Text)
type AttrLabel NumerableIconLabelPropertyInfo = "label"
type AttrOrigin NumerableIconLabelPropertyInfo = NumerableIcon
attrGet = getNumerableIconLabel
attrSet = setNumerableIconLabel
attrTransfer _ v = do
return v
attrConstruct = constructNumerableIconLabel
attrClear = clearNumerableIconLabel
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.NumerableIcon.label"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-NumerableIcon.html#g:attr:label"
})
#endif
getNumerableIconStyleContext :: (MonadIO m, IsNumerableIcon o) => o -> m (Maybe Gtk.StyleContext.StyleContext)
getNumerableIconStyleContext :: forall (m :: * -> *) o.
(MonadIO m, IsNumerableIcon o) =>
o -> m (Maybe StyleContext)
getNumerableIconStyleContext o
obj = IO (Maybe StyleContext) -> m (Maybe StyleContext)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe StyleContext) -> m (Maybe StyleContext))
-> IO (Maybe StyleContext) -> m (Maybe StyleContext)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr StyleContext -> StyleContext)
-> IO (Maybe StyleContext)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"style-context" ManagedPtr StyleContext -> StyleContext
Gtk.StyleContext.StyleContext
setNumerableIconStyleContext :: (MonadIO m, IsNumerableIcon o, Gtk.StyleContext.IsStyleContext a) => o -> a -> m ()
setNumerableIconStyleContext :: forall (m :: * -> *) o a.
(MonadIO m, IsNumerableIcon o, IsStyleContext a) =>
o -> a -> m ()
setNumerableIconStyleContext o
obj a
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"style-context" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructNumerableIconStyleContext :: (IsNumerableIcon o, MIO.MonadIO m, Gtk.StyleContext.IsStyleContext a) => a -> m (GValueConstruct o)
constructNumerableIconStyleContext :: forall o (m :: * -> *) a.
(IsNumerableIcon o, MonadIO m, IsStyleContext a) =>
a -> m (GValueConstruct o)
constructNumerableIconStyleContext a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"style-context" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
#if defined(ENABLE_OVERLOADING)
data NumerableIconStyleContextPropertyInfo
instance AttrInfo NumerableIconStyleContextPropertyInfo where
type AttrAllowedOps NumerableIconStyleContextPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint NumerableIconStyleContextPropertyInfo = IsNumerableIcon
type AttrSetTypeConstraint NumerableIconStyleContextPropertyInfo = Gtk.StyleContext.IsStyleContext
type AttrTransferTypeConstraint NumerableIconStyleContextPropertyInfo = Gtk.StyleContext.IsStyleContext
type AttrTransferType NumerableIconStyleContextPropertyInfo = Gtk.StyleContext.StyleContext
type AttrGetType NumerableIconStyleContextPropertyInfo = (Maybe Gtk.StyleContext.StyleContext)
type AttrLabel NumerableIconStyleContextPropertyInfo = "style-context"
type AttrOrigin NumerableIconStyleContextPropertyInfo = NumerableIcon
attrGet = getNumerableIconStyleContext
attrSet = setNumerableIconStyleContext
attrTransfer _ v = do
unsafeCastTo Gtk.StyleContext.StyleContext v
attrConstruct = constructNumerableIconStyleContext
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.NumerableIcon.styleContext"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-NumerableIcon.html#g:attr:styleContext"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList NumerableIcon
type instance O.AttributeList NumerableIcon = NumerableIconAttributeList
type NumerableIconAttributeList = ('[ '("backgroundIcon", NumerableIconBackgroundIconPropertyInfo), '("backgroundIconName", NumerableIconBackgroundIconNamePropertyInfo), '("count", NumerableIconCountPropertyInfo), '("gicon", Gio.EmblemedIcon.EmblemedIconGiconPropertyInfo), '("label", NumerableIconLabelPropertyInfo), '("styleContext", NumerableIconStyleContextPropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
numerableIconBackgroundIcon :: AttrLabelProxy "backgroundIcon"
numerableIconBackgroundIcon = AttrLabelProxy
numerableIconBackgroundIconName :: AttrLabelProxy "backgroundIconName"
numerableIconBackgroundIconName = AttrLabelProxy
numerableIconCount :: AttrLabelProxy "count"
numerableIconCount = AttrLabelProxy
numerableIconLabel :: AttrLabelProxy "label"
numerableIconLabel = AttrLabelProxy
numerableIconStyleContext :: AttrLabelProxy "styleContext"
numerableIconStyleContext = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList NumerableIcon = NumerableIconSignalList
type NumerableIconSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "gtk_numerable_icon_get_background_gicon" gtk_numerable_icon_get_background_gicon ::
Ptr NumerableIcon ->
IO (Ptr Gio.Icon.Icon)
{-# DEPRECATED numerableIconGetBackgroundGicon ["(Since version 3.14)"] #-}
numerableIconGetBackgroundGicon ::
(B.CallStack.HasCallStack, MonadIO m, IsNumerableIcon a) =>
a
-> m (Maybe Gio.Icon.Icon)
numerableIconGetBackgroundGicon :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsNumerableIcon a) =>
a -> m (Maybe Icon)
numerableIconGetBackgroundGicon a
self = IO (Maybe Icon) -> m (Maybe Icon)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Icon) -> m (Maybe Icon))
-> IO (Maybe Icon) -> m (Maybe Icon)
forall a b. (a -> b) -> a -> b
$ do
Ptr NumerableIcon
self' <- a -> IO (Ptr NumerableIcon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr Icon
result <- Ptr NumerableIcon -> IO (Ptr Icon)
gtk_numerable_icon_get_background_gicon Ptr NumerableIcon
self'
Maybe Icon
maybeResult <- Ptr Icon -> (Ptr Icon -> IO Icon) -> IO (Maybe Icon)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Icon
result ((Ptr Icon -> IO Icon) -> IO (Maybe Icon))
-> (Ptr Icon -> IO Icon) -> IO (Maybe Icon)
forall a b. (a -> b) -> a -> b
$ \Ptr Icon
result' -> do
Icon
result'' <- ((ManagedPtr Icon -> Icon) -> Ptr Icon -> IO Icon
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Icon -> Icon
Gio.Icon.Icon) Ptr Icon
result'
Icon -> IO Icon
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Icon
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
Maybe Icon -> IO (Maybe Icon)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Icon
maybeResult
#if defined(ENABLE_OVERLOADING)
data NumerableIconGetBackgroundGiconMethodInfo
instance (signature ~ (m (Maybe Gio.Icon.Icon)), MonadIO m, IsNumerableIcon a) => O.OverloadedMethod NumerableIconGetBackgroundGiconMethodInfo a signature where
overloadedMethod = numerableIconGetBackgroundGicon
instance O.OverloadedMethodInfo NumerableIconGetBackgroundGiconMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.NumerableIcon.numerableIconGetBackgroundGicon",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-NumerableIcon.html#v:numerableIconGetBackgroundGicon"
})
#endif
foreign import ccall "gtk_numerable_icon_get_background_icon_name" gtk_numerable_icon_get_background_icon_name ::
Ptr NumerableIcon ->
IO CString
{-# DEPRECATED numerableIconGetBackgroundIconName ["(Since version 3.14)"] #-}
numerableIconGetBackgroundIconName ::
(B.CallStack.HasCallStack, MonadIO m, IsNumerableIcon a) =>
a
-> m (Maybe T.Text)
numerableIconGetBackgroundIconName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsNumerableIcon a) =>
a -> m (Maybe Text)
numerableIconGetBackgroundIconName a
self = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
Ptr NumerableIcon
self' <- a -> IO (Ptr NumerableIcon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
result <- Ptr NumerableIcon -> IO CString
gtk_numerable_icon_get_background_icon_name Ptr NumerableIcon
self'
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
$ \CString
result' -> do
Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult
#if defined(ENABLE_OVERLOADING)
data NumerableIconGetBackgroundIconNameMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsNumerableIcon a) => O.OverloadedMethod NumerableIconGetBackgroundIconNameMethodInfo a signature where
overloadedMethod = numerableIconGetBackgroundIconName
instance O.OverloadedMethodInfo NumerableIconGetBackgroundIconNameMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.NumerableIcon.numerableIconGetBackgroundIconName",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-NumerableIcon.html#v:numerableIconGetBackgroundIconName"
})
#endif
foreign import ccall "gtk_numerable_icon_get_count" gtk_numerable_icon_get_count ::
Ptr NumerableIcon ->
IO Int32
{-# DEPRECATED numerableIconGetCount ["(Since version 3.14)"] #-}
numerableIconGetCount ::
(B.CallStack.HasCallStack, MonadIO m, IsNumerableIcon a) =>
a
-> m Int32
numerableIconGetCount :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsNumerableIcon a) =>
a -> m Int32
numerableIconGetCount a
self = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
Ptr NumerableIcon
self' <- a -> IO (Ptr NumerableIcon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Int32
result <- Ptr NumerableIcon -> IO Int32
gtk_numerable_icon_get_count Ptr NumerableIcon
self'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data NumerableIconGetCountMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsNumerableIcon a) => O.OverloadedMethod NumerableIconGetCountMethodInfo a signature where
overloadedMethod = numerableIconGetCount
instance O.OverloadedMethodInfo NumerableIconGetCountMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.NumerableIcon.numerableIconGetCount",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-NumerableIcon.html#v:numerableIconGetCount"
})
#endif
foreign import ccall "gtk_numerable_icon_get_label" gtk_numerable_icon_get_label ::
Ptr NumerableIcon ->
IO CString
{-# DEPRECATED numerableIconGetLabel ["(Since version 3.14)"] #-}
numerableIconGetLabel ::
(B.CallStack.HasCallStack, MonadIO m, IsNumerableIcon a) =>
a
-> m (Maybe T.Text)
numerableIconGetLabel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsNumerableIcon a) =>
a -> m (Maybe Text)
numerableIconGetLabel a
self = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
Ptr NumerableIcon
self' <- a -> IO (Ptr NumerableIcon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
result <- Ptr NumerableIcon -> IO CString
gtk_numerable_icon_get_label Ptr NumerableIcon
self'
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
$ \CString
result' -> do
Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult
#if defined(ENABLE_OVERLOADING)
data NumerableIconGetLabelMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsNumerableIcon a) => O.OverloadedMethod NumerableIconGetLabelMethodInfo a signature where
overloadedMethod = numerableIconGetLabel
instance O.OverloadedMethodInfo NumerableIconGetLabelMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.NumerableIcon.numerableIconGetLabel",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-NumerableIcon.html#v:numerableIconGetLabel"
})
#endif
foreign import ccall "gtk_numerable_icon_get_style_context" gtk_numerable_icon_get_style_context ::
Ptr NumerableIcon ->
IO (Ptr Gtk.StyleContext.StyleContext)
{-# DEPRECATED numerableIconGetStyleContext ["(Since version 3.14)"] #-}
numerableIconGetStyleContext ::
(B.CallStack.HasCallStack, MonadIO m, IsNumerableIcon a) =>
a
-> m (Maybe Gtk.StyleContext.StyleContext)
numerableIconGetStyleContext :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsNumerableIcon a) =>
a -> m (Maybe StyleContext)
numerableIconGetStyleContext a
self = IO (Maybe StyleContext) -> m (Maybe StyleContext)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe StyleContext) -> m (Maybe StyleContext))
-> IO (Maybe StyleContext) -> m (Maybe StyleContext)
forall a b. (a -> b) -> a -> b
$ do
Ptr NumerableIcon
self' <- a -> IO (Ptr NumerableIcon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr StyleContext
result <- Ptr NumerableIcon -> IO (Ptr StyleContext)
gtk_numerable_icon_get_style_context Ptr NumerableIcon
self'
Maybe StyleContext
maybeResult <- Ptr StyleContext
-> (Ptr StyleContext -> IO StyleContext) -> IO (Maybe StyleContext)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr StyleContext
result ((Ptr StyleContext -> IO StyleContext) -> IO (Maybe StyleContext))
-> (Ptr StyleContext -> IO StyleContext) -> IO (Maybe StyleContext)
forall a b. (a -> b) -> a -> b
$ \Ptr StyleContext
result' -> do
StyleContext
result'' <- ((ManagedPtr StyleContext -> StyleContext)
-> Ptr StyleContext -> IO StyleContext
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr StyleContext -> StyleContext
Gtk.StyleContext.StyleContext) Ptr StyleContext
result'
StyleContext -> IO StyleContext
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return StyleContext
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
Maybe StyleContext -> IO (Maybe StyleContext)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe StyleContext
maybeResult
#if defined(ENABLE_OVERLOADING)
data NumerableIconGetStyleContextMethodInfo
instance (signature ~ (m (Maybe Gtk.StyleContext.StyleContext)), MonadIO m, IsNumerableIcon a) => O.OverloadedMethod NumerableIconGetStyleContextMethodInfo a signature where
overloadedMethod = numerableIconGetStyleContext
instance O.OverloadedMethodInfo NumerableIconGetStyleContextMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.NumerableIcon.numerableIconGetStyleContext",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-NumerableIcon.html#v:numerableIconGetStyleContext"
})
#endif
foreign import ccall "gtk_numerable_icon_set_background_gicon" gtk_numerable_icon_set_background_gicon ::
Ptr NumerableIcon ->
Ptr Gio.Icon.Icon ->
IO ()
{-# DEPRECATED numerableIconSetBackgroundGicon ["(Since version 3.14)"] #-}
numerableIconSetBackgroundGicon ::
(B.CallStack.HasCallStack, MonadIO m, IsNumerableIcon a, Gio.Icon.IsIcon b) =>
a
-> Maybe (b)
-> m ()
numerableIconSetBackgroundGicon :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsNumerableIcon a, IsIcon b) =>
a -> Maybe b -> m ()
numerableIconSetBackgroundGicon a
self Maybe b
icon = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr NumerableIcon
self' <- a -> IO (Ptr NumerableIcon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr Icon
maybeIcon <- case Maybe b
icon of
Maybe b
Nothing -> Ptr Icon -> IO (Ptr Icon)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Icon
forall a. Ptr a
nullPtr
Just b
jIcon -> do
Ptr Icon
jIcon' <- b -> IO (Ptr Icon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jIcon
Ptr Icon -> IO (Ptr Icon)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Icon
jIcon'
Ptr NumerableIcon -> Ptr Icon -> IO ()
gtk_numerable_icon_set_background_gicon Ptr NumerableIcon
self' Ptr Icon
maybeIcon
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
icon b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data NumerableIconSetBackgroundGiconMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsNumerableIcon a, Gio.Icon.IsIcon b) => O.OverloadedMethod NumerableIconSetBackgroundGiconMethodInfo a signature where
overloadedMethod = numerableIconSetBackgroundGicon
instance O.OverloadedMethodInfo NumerableIconSetBackgroundGiconMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.NumerableIcon.numerableIconSetBackgroundGicon",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-NumerableIcon.html#v:numerableIconSetBackgroundGicon"
})
#endif
foreign import ccall "gtk_numerable_icon_set_background_icon_name" gtk_numerable_icon_set_background_icon_name ::
Ptr NumerableIcon ->
CString ->
IO ()
{-# DEPRECATED numerableIconSetBackgroundIconName ["(Since version 3.14)"] #-}
numerableIconSetBackgroundIconName ::
(B.CallStack.HasCallStack, MonadIO m, IsNumerableIcon a) =>
a
-> Maybe (T.Text)
-> m ()
numerableIconSetBackgroundIconName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsNumerableIcon a) =>
a -> Maybe Text -> m ()
numerableIconSetBackgroundIconName a
self Maybe Text
iconName = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr NumerableIcon
self' <- a -> IO (Ptr NumerableIcon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
maybeIconName <- case Maybe Text
iconName of
Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
Just Text
jIconName -> do
CString
jIconName' <- Text -> IO CString
textToCString Text
jIconName
CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jIconName'
Ptr NumerableIcon -> CString -> IO ()
gtk_numerable_icon_set_background_icon_name Ptr NumerableIcon
self' CString
maybeIconName
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeIconName
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data NumerableIconSetBackgroundIconNameMethodInfo
instance (signature ~ (Maybe (T.Text) -> m ()), MonadIO m, IsNumerableIcon a) => O.OverloadedMethod NumerableIconSetBackgroundIconNameMethodInfo a signature where
overloadedMethod = numerableIconSetBackgroundIconName
instance O.OverloadedMethodInfo NumerableIconSetBackgroundIconNameMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.NumerableIcon.numerableIconSetBackgroundIconName",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-NumerableIcon.html#v:numerableIconSetBackgroundIconName"
})
#endif
foreign import ccall "gtk_numerable_icon_set_count" gtk_numerable_icon_set_count ::
Ptr NumerableIcon ->
Int32 ->
IO ()
{-# DEPRECATED numerableIconSetCount ["(Since version 3.14)"] #-}
numerableIconSetCount ::
(B.CallStack.HasCallStack, MonadIO m, IsNumerableIcon a) =>
a
-> Int32
-> m ()
numerableIconSetCount :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsNumerableIcon a) =>
a -> Int32 -> m ()
numerableIconSetCount a
self Int32
count = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr NumerableIcon
self' <- a -> IO (Ptr NumerableIcon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr NumerableIcon -> Int32 -> IO ()
gtk_numerable_icon_set_count Ptr NumerableIcon
self' Int32
count
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data NumerableIconSetCountMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsNumerableIcon a) => O.OverloadedMethod NumerableIconSetCountMethodInfo a signature where
overloadedMethod = numerableIconSetCount
instance O.OverloadedMethodInfo NumerableIconSetCountMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.NumerableIcon.numerableIconSetCount",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-NumerableIcon.html#v:numerableIconSetCount"
})
#endif
foreign import ccall "gtk_numerable_icon_set_label" gtk_numerable_icon_set_label ::
Ptr NumerableIcon ->
CString ->
IO ()
{-# DEPRECATED numerableIconSetLabel ["(Since version 3.14)"] #-}
numerableIconSetLabel ::
(B.CallStack.HasCallStack, MonadIO m, IsNumerableIcon a) =>
a
-> Maybe (T.Text)
-> m ()
numerableIconSetLabel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsNumerableIcon a) =>
a -> Maybe Text -> m ()
numerableIconSetLabel a
self Maybe Text
label = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr NumerableIcon
self' <- a -> IO (Ptr NumerableIcon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
maybeLabel <- case Maybe Text
label of
Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
Just Text
jLabel -> do
CString
jLabel' <- Text -> IO CString
textToCString Text
jLabel
CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jLabel'
Ptr NumerableIcon -> CString -> IO ()
gtk_numerable_icon_set_label Ptr NumerableIcon
self' CString
maybeLabel
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeLabel
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data NumerableIconSetLabelMethodInfo
instance (signature ~ (Maybe (T.Text) -> m ()), MonadIO m, IsNumerableIcon a) => O.OverloadedMethod NumerableIconSetLabelMethodInfo a signature where
overloadedMethod = numerableIconSetLabel
instance O.OverloadedMethodInfo NumerableIconSetLabelMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.NumerableIcon.numerableIconSetLabel",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-NumerableIcon.html#v:numerableIconSetLabel"
})
#endif
foreign import ccall "gtk_numerable_icon_set_style_context" gtk_numerable_icon_set_style_context ::
Ptr NumerableIcon ->
Ptr Gtk.StyleContext.StyleContext ->
IO ()
{-# DEPRECATED numerableIconSetStyleContext ["(Since version 3.14)"] #-}
numerableIconSetStyleContext ::
(B.CallStack.HasCallStack, MonadIO m, IsNumerableIcon a, Gtk.StyleContext.IsStyleContext b) =>
a
-> b
-> m ()
numerableIconSetStyleContext :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsNumerableIcon a, IsStyleContext b) =>
a -> b -> m ()
numerableIconSetStyleContext a
self b
style = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr NumerableIcon
self' <- a -> IO (Ptr NumerableIcon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr StyleContext
style' <- b -> IO (Ptr StyleContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
style
Ptr NumerableIcon -> Ptr StyleContext -> IO ()
gtk_numerable_icon_set_style_context Ptr NumerableIcon
self' Ptr StyleContext
style'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
style
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data NumerableIconSetStyleContextMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsNumerableIcon a, Gtk.StyleContext.IsStyleContext b) => O.OverloadedMethod NumerableIconSetStyleContextMethodInfo a signature where
overloadedMethod = numerableIconSetStyleContext
instance O.OverloadedMethodInfo NumerableIconSetStyleContextMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.NumerableIcon.numerableIconSetStyleContext",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-NumerableIcon.html#v:numerableIconSetStyleContext"
})
#endif
foreign import ccall "gtk_numerable_icon_new" gtk_numerable_icon_new ::
Ptr Gio.Icon.Icon ->
IO (Ptr Gio.Icon.Icon)
{-# DEPRECATED numerableIconNew ["(Since version 3.14)"] #-}
numerableIconNew ::
(B.CallStack.HasCallStack, MonadIO m, Gio.Icon.IsIcon a) =>
a
-> m Gio.Icon.Icon
numerableIconNew :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIcon a) =>
a -> m Icon
numerableIconNew a
baseIcon = IO Icon -> m Icon
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Icon -> m Icon) -> IO Icon -> m Icon
forall a b. (a -> b) -> a -> b
$ do
Ptr Icon
baseIcon' <- a -> IO (Ptr Icon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
baseIcon
Ptr Icon
result <- Ptr Icon -> IO (Ptr Icon)
gtk_numerable_icon_new Ptr Icon
baseIcon'
Text -> Ptr Icon -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"numerableIconNew" Ptr Icon
result
Icon
result' <- ((ManagedPtr Icon -> Icon) -> Ptr Icon -> IO Icon
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Icon -> Icon
Gio.Icon.Icon) Ptr Icon
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
baseIcon
Icon -> IO Icon
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Icon
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_numerable_icon_new_with_style_context" gtk_numerable_icon_new_with_style_context ::
Ptr Gio.Icon.Icon ->
Ptr Gtk.StyleContext.StyleContext ->
IO (Ptr Gio.Icon.Icon)
{-# DEPRECATED numerableIconNewWithStyleContext ["(Since version 3.14)"] #-}
numerableIconNewWithStyleContext ::
(B.CallStack.HasCallStack, MonadIO m, Gio.Icon.IsIcon a, Gtk.StyleContext.IsStyleContext b) =>
a
-> b
-> m Gio.Icon.Icon
numerableIconNewWithStyleContext :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsIcon a, IsStyleContext b) =>
a -> b -> m Icon
numerableIconNewWithStyleContext a
baseIcon b
context = IO Icon -> m Icon
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Icon -> m Icon) -> IO Icon -> m Icon
forall a b. (a -> b) -> a -> b
$ do
Ptr Icon
baseIcon' <- a -> IO (Ptr Icon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
baseIcon
Ptr StyleContext
context' <- b -> IO (Ptr StyleContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
context
Ptr Icon
result <- Ptr Icon -> Ptr StyleContext -> IO (Ptr Icon)
gtk_numerable_icon_new_with_style_context Ptr Icon
baseIcon' Ptr StyleContext
context'
Text -> Ptr Icon -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"numerableIconNewWithStyleContext" Ptr Icon
result
Icon
result' <- ((ManagedPtr Icon -> Icon) -> Ptr Icon -> IO Icon
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Icon -> Icon
Gio.Icon.Icon) Ptr Icon
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
baseIcon
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
context
Icon -> IO Icon
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Icon
result'
#if defined(ENABLE_OVERLOADING)
#endif