{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Objects.CellRendererPixbuf
(
CellRendererPixbuf(..) ,
IsCellRendererPixbuf ,
toCellRendererPixbuf ,
noCellRendererPixbuf ,
#if defined(ENABLE_OVERLOADING)
ResolveCellRendererPixbufMethod ,
#endif
cellRendererPixbufNew ,
#if defined(ENABLE_OVERLOADING)
CellRendererPixbufFollowStatePropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
cellRendererPixbufFollowState ,
#endif
constructCellRendererPixbufFollowState ,
getCellRendererPixbufFollowState ,
setCellRendererPixbufFollowState ,
#if defined(ENABLE_OVERLOADING)
CellRendererPixbufGiconPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
cellRendererPixbufGicon ,
#endif
clearCellRendererPixbufGicon ,
constructCellRendererPixbufGicon ,
getCellRendererPixbufGicon ,
setCellRendererPixbufGicon ,
#if defined(ENABLE_OVERLOADING)
CellRendererPixbufIconNamePropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
cellRendererPixbufIconName ,
#endif
clearCellRendererPixbufIconName ,
constructCellRendererPixbufIconName ,
getCellRendererPixbufIconName ,
setCellRendererPixbufIconName ,
#if defined(ENABLE_OVERLOADING)
CellRendererPixbufPixbufPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
cellRendererPixbufPixbuf ,
#endif
clearCellRendererPixbufPixbuf ,
constructCellRendererPixbufPixbuf ,
getCellRendererPixbufPixbuf ,
setCellRendererPixbufPixbuf ,
#if defined(ENABLE_OVERLOADING)
CellRendererPixbufPixbufExpanderClosedPropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
cellRendererPixbufPixbufExpanderClosed ,
#endif
clearCellRendererPixbufPixbufExpanderClosed,
constructCellRendererPixbufPixbufExpanderClosed,
getCellRendererPixbufPixbufExpanderClosed,
setCellRendererPixbufPixbufExpanderClosed,
#if defined(ENABLE_OVERLOADING)
CellRendererPixbufPixbufExpanderOpenPropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
cellRendererPixbufPixbufExpanderOpen ,
#endif
clearCellRendererPixbufPixbufExpanderOpen,
constructCellRendererPixbufPixbufExpanderOpen,
getCellRendererPixbufPixbufExpanderOpen ,
setCellRendererPixbufPixbufExpanderOpen ,
#if defined(ENABLE_OVERLOADING)
CellRendererPixbufStockDetailPropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
cellRendererPixbufStockDetail ,
#endif
clearCellRendererPixbufStockDetail ,
constructCellRendererPixbufStockDetail ,
getCellRendererPixbufStockDetail ,
setCellRendererPixbufStockDetail ,
#if defined(ENABLE_OVERLOADING)
CellRendererPixbufStockIdPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
cellRendererPixbufStockId ,
#endif
clearCellRendererPixbufStockId ,
constructCellRendererPixbufStockId ,
getCellRendererPixbufStockId ,
setCellRendererPixbufStockId ,
#if defined(ENABLE_OVERLOADING)
CellRendererPixbufStockSizePropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
cellRendererPixbufStockSize ,
#endif
constructCellRendererPixbufStockSize ,
getCellRendererPixbufStockSize ,
setCellRendererPixbufStockSize ,
#if defined(ENABLE_OVERLOADING)
CellRendererPixbufSurfacePropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
cellRendererPixbufSurface ,
#endif
clearCellRendererPixbufSurface ,
constructCellRendererPixbufSurface ,
getCellRendererPixbufSurface ,
setCellRendererPixbufSurface ,
) 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.GdkPixbuf.Objects.Pixbuf as GdkPixbuf.Pixbuf
import qualified GI.Gio.Interfaces.Icon as Gio.Icon
import {-# SOURCE #-} qualified GI.Gtk.Objects.CellRenderer as Gtk.CellRenderer
newtype CellRendererPixbuf = CellRendererPixbuf (ManagedPtr CellRendererPixbuf)
deriving (CellRendererPixbuf -> CellRendererPixbuf -> Bool
(CellRendererPixbuf -> CellRendererPixbuf -> Bool)
-> (CellRendererPixbuf -> CellRendererPixbuf -> Bool)
-> Eq CellRendererPixbuf
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CellRendererPixbuf -> CellRendererPixbuf -> Bool
$c/= :: CellRendererPixbuf -> CellRendererPixbuf -> Bool
== :: CellRendererPixbuf -> CellRendererPixbuf -> Bool
$c== :: CellRendererPixbuf -> CellRendererPixbuf -> Bool
Eq)
foreign import ccall "gtk_cell_renderer_pixbuf_get_type"
c_gtk_cell_renderer_pixbuf_get_type :: IO GType
instance GObject CellRendererPixbuf where
gobjectType :: IO GType
gobjectType = IO GType
c_gtk_cell_renderer_pixbuf_get_type
instance B.GValue.IsGValue CellRendererPixbuf where
toGValue :: CellRendererPixbuf -> IO GValue
toGValue o :: CellRendererPixbuf
o = do
GType
gtype <- IO GType
c_gtk_cell_renderer_pixbuf_get_type
CellRendererPixbuf
-> (Ptr CellRendererPixbuf -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr CellRendererPixbuf
o (GType
-> (GValue -> Ptr CellRendererPixbuf -> IO ())
-> Ptr CellRendererPixbuf
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr CellRendererPixbuf -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO CellRendererPixbuf
fromGValue gv :: GValue
gv = do
Ptr CellRendererPixbuf
ptr <- GValue -> IO (Ptr CellRendererPixbuf)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr CellRendererPixbuf)
(ManagedPtr CellRendererPixbuf -> CellRendererPixbuf)
-> Ptr CellRendererPixbuf -> IO CellRendererPixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr CellRendererPixbuf -> CellRendererPixbuf
CellRendererPixbuf Ptr CellRendererPixbuf
ptr
class (GObject o, O.IsDescendantOf CellRendererPixbuf o) => IsCellRendererPixbuf o
instance (GObject o, O.IsDescendantOf CellRendererPixbuf o) => IsCellRendererPixbuf o
instance O.HasParentTypes CellRendererPixbuf
type instance O.ParentTypes CellRendererPixbuf = '[Gtk.CellRenderer.CellRenderer, GObject.Object.Object]
toCellRendererPixbuf :: (MonadIO m, IsCellRendererPixbuf o) => o -> m CellRendererPixbuf
toCellRendererPixbuf :: o -> m CellRendererPixbuf
toCellRendererPixbuf = IO CellRendererPixbuf -> m CellRendererPixbuf
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CellRendererPixbuf -> m CellRendererPixbuf)
-> (o -> IO CellRendererPixbuf) -> o -> m CellRendererPixbuf
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr CellRendererPixbuf -> CellRendererPixbuf)
-> o -> IO CellRendererPixbuf
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr CellRendererPixbuf -> CellRendererPixbuf
CellRendererPixbuf
noCellRendererPixbuf :: Maybe CellRendererPixbuf
noCellRendererPixbuf :: Maybe CellRendererPixbuf
noCellRendererPixbuf = Maybe CellRendererPixbuf
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveCellRendererPixbufMethod (t :: Symbol) (o :: *) :: * where
ResolveCellRendererPixbufMethod "activate" o = Gtk.CellRenderer.CellRendererActivateMethodInfo
ResolveCellRendererPixbufMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveCellRendererPixbufMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveCellRendererPixbufMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveCellRendererPixbufMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveCellRendererPixbufMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveCellRendererPixbufMethod "isActivatable" o = Gtk.CellRenderer.CellRendererIsActivatableMethodInfo
ResolveCellRendererPixbufMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveCellRendererPixbufMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveCellRendererPixbufMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveCellRendererPixbufMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveCellRendererPixbufMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveCellRendererPixbufMethod "render" o = Gtk.CellRenderer.CellRendererRenderMethodInfo
ResolveCellRendererPixbufMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveCellRendererPixbufMethod "startEditing" o = Gtk.CellRenderer.CellRendererStartEditingMethodInfo
ResolveCellRendererPixbufMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveCellRendererPixbufMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveCellRendererPixbufMethod "stopEditing" o = Gtk.CellRenderer.CellRendererStopEditingMethodInfo
ResolveCellRendererPixbufMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveCellRendererPixbufMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveCellRendererPixbufMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveCellRendererPixbufMethod "getAlignedArea" o = Gtk.CellRenderer.CellRendererGetAlignedAreaMethodInfo
ResolveCellRendererPixbufMethod "getAlignment" o = Gtk.CellRenderer.CellRendererGetAlignmentMethodInfo
ResolveCellRendererPixbufMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveCellRendererPixbufMethod "getFixedSize" o = Gtk.CellRenderer.CellRendererGetFixedSizeMethodInfo
ResolveCellRendererPixbufMethod "getPadding" o = Gtk.CellRenderer.CellRendererGetPaddingMethodInfo
ResolveCellRendererPixbufMethod "getPreferredHeight" o = Gtk.CellRenderer.CellRendererGetPreferredHeightMethodInfo
ResolveCellRendererPixbufMethod "getPreferredHeightForWidth" o = Gtk.CellRenderer.CellRendererGetPreferredHeightForWidthMethodInfo
ResolveCellRendererPixbufMethod "getPreferredSize" o = Gtk.CellRenderer.CellRendererGetPreferredSizeMethodInfo
ResolveCellRendererPixbufMethod "getPreferredWidth" o = Gtk.CellRenderer.CellRendererGetPreferredWidthMethodInfo
ResolveCellRendererPixbufMethod "getPreferredWidthForHeight" o = Gtk.CellRenderer.CellRendererGetPreferredWidthForHeightMethodInfo
ResolveCellRendererPixbufMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveCellRendererPixbufMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveCellRendererPixbufMethod "getRequestMode" o = Gtk.CellRenderer.CellRendererGetRequestModeMethodInfo
ResolveCellRendererPixbufMethod "getSensitive" o = Gtk.CellRenderer.CellRendererGetSensitiveMethodInfo
ResolveCellRendererPixbufMethod "getSize" o = Gtk.CellRenderer.CellRendererGetSizeMethodInfo
ResolveCellRendererPixbufMethod "getState" o = Gtk.CellRenderer.CellRendererGetStateMethodInfo
ResolveCellRendererPixbufMethod "getVisible" o = Gtk.CellRenderer.CellRendererGetVisibleMethodInfo
ResolveCellRendererPixbufMethod "setAlignment" o = Gtk.CellRenderer.CellRendererSetAlignmentMethodInfo
ResolveCellRendererPixbufMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveCellRendererPixbufMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveCellRendererPixbufMethod "setFixedSize" o = Gtk.CellRenderer.CellRendererSetFixedSizeMethodInfo
ResolveCellRendererPixbufMethod "setPadding" o = Gtk.CellRenderer.CellRendererSetPaddingMethodInfo
ResolveCellRendererPixbufMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveCellRendererPixbufMethod "setSensitive" o = Gtk.CellRenderer.CellRendererSetSensitiveMethodInfo
ResolveCellRendererPixbufMethod "setVisible" o = Gtk.CellRenderer.CellRendererSetVisibleMethodInfo
ResolveCellRendererPixbufMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveCellRendererPixbufMethod t CellRendererPixbuf, O.MethodInfo info CellRendererPixbuf p) => OL.IsLabel t (CellRendererPixbuf -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
getCellRendererPixbufFollowState :: (MonadIO m, IsCellRendererPixbuf o) => o -> m Bool
getCellRendererPixbufFollowState :: o -> m Bool
getCellRendererPixbufFollowState obj :: o
obj = 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
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj "follow-state"
setCellRendererPixbufFollowState :: (MonadIO m, IsCellRendererPixbuf o) => o -> Bool -> m ()
setCellRendererPixbufFollowState :: o -> Bool -> m ()
setCellRendererPixbufFollowState obj :: o
obj val :: Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj "follow-state" Bool
val
constructCellRendererPixbufFollowState :: (IsCellRendererPixbuf o) => Bool -> IO (GValueConstruct o)
constructCellRendererPixbufFollowState :: Bool -> IO (GValueConstruct o)
constructCellRendererPixbufFollowState val :: Bool
val = String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool "follow-state" Bool
val
#if defined(ENABLE_OVERLOADING)
data CellRendererPixbufFollowStatePropertyInfo
instance AttrInfo CellRendererPixbufFollowStatePropertyInfo where
type AttrAllowedOps CellRendererPixbufFollowStatePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint CellRendererPixbufFollowStatePropertyInfo = IsCellRendererPixbuf
type AttrSetTypeConstraint CellRendererPixbufFollowStatePropertyInfo = (~) Bool
type AttrTransferTypeConstraint CellRendererPixbufFollowStatePropertyInfo = (~) Bool
type AttrTransferType CellRendererPixbufFollowStatePropertyInfo = Bool
type AttrGetType CellRendererPixbufFollowStatePropertyInfo = Bool
type AttrLabel CellRendererPixbufFollowStatePropertyInfo = "follow-state"
type AttrOrigin CellRendererPixbufFollowStatePropertyInfo = CellRendererPixbuf
attrGet = getCellRendererPixbufFollowState
attrSet = setCellRendererPixbufFollowState
attrTransfer _ v = do
return v
attrConstruct = constructCellRendererPixbufFollowState
attrClear = undefined
#endif
getCellRendererPixbufGicon :: (MonadIO m, IsCellRendererPixbuf o) => o -> m (Maybe Gio.Icon.Icon)
getCellRendererPixbufGicon :: o -> m (Maybe Icon)
getCellRendererPixbufGicon obj :: o
obj = IO (Maybe Icon) -> m (Maybe Icon)
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
$ 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 "gicon" ManagedPtr Icon -> Icon
Gio.Icon.Icon
setCellRendererPixbufGicon :: (MonadIO m, IsCellRendererPixbuf o, Gio.Icon.IsIcon a) => o -> a -> m ()
setCellRendererPixbufGicon :: o -> a -> m ()
setCellRendererPixbufGicon obj :: o
obj val :: a
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj "gicon" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructCellRendererPixbufGicon :: (IsCellRendererPixbuf o, Gio.Icon.IsIcon a) => a -> IO (GValueConstruct o)
constructCellRendererPixbufGicon :: a -> IO (GValueConstruct o)
constructCellRendererPixbufGicon val :: a
val = String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject "gicon" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
clearCellRendererPixbufGicon :: (MonadIO m, IsCellRendererPixbuf o) => o -> m ()
clearCellRendererPixbufGicon :: o -> m ()
clearCellRendererPixbufGicon obj :: o
obj = IO () -> m ()
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 "gicon" (Maybe Icon
forall a. Maybe a
Nothing :: Maybe Gio.Icon.Icon)
#if defined(ENABLE_OVERLOADING)
data CellRendererPixbufGiconPropertyInfo
instance AttrInfo CellRendererPixbufGiconPropertyInfo where
type AttrAllowedOps CellRendererPixbufGiconPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint CellRendererPixbufGiconPropertyInfo = IsCellRendererPixbuf
type AttrSetTypeConstraint CellRendererPixbufGiconPropertyInfo = Gio.Icon.IsIcon
type AttrTransferTypeConstraint CellRendererPixbufGiconPropertyInfo = Gio.Icon.IsIcon
type AttrTransferType CellRendererPixbufGiconPropertyInfo = Gio.Icon.Icon
type AttrGetType CellRendererPixbufGiconPropertyInfo = (Maybe Gio.Icon.Icon)
type AttrLabel CellRendererPixbufGiconPropertyInfo = "gicon"
type AttrOrigin CellRendererPixbufGiconPropertyInfo = CellRendererPixbuf
attrGet = getCellRendererPixbufGicon
attrSet = setCellRendererPixbufGicon
attrTransfer _ v = do
unsafeCastTo Gio.Icon.Icon v
attrConstruct = constructCellRendererPixbufGicon
attrClear = clearCellRendererPixbufGicon
#endif
getCellRendererPixbufIconName :: (MonadIO m, IsCellRendererPixbuf o) => o -> m (Maybe T.Text)
getCellRendererPixbufIconName :: o -> m (Maybe Text)
getCellRendererPixbufIconName obj :: o
obj = 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
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj "icon-name"
setCellRendererPixbufIconName :: (MonadIO m, IsCellRendererPixbuf o) => o -> T.Text -> m ()
setCellRendererPixbufIconName :: o -> Text -> m ()
setCellRendererPixbufIconName obj :: o
obj val :: Text
val = IO () -> m ()
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 "icon-name" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructCellRendererPixbufIconName :: (IsCellRendererPixbuf o) => T.Text -> IO (GValueConstruct o)
constructCellRendererPixbufIconName :: Text -> IO (GValueConstruct o)
constructCellRendererPixbufIconName val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "icon-name" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
clearCellRendererPixbufIconName :: (MonadIO m, IsCellRendererPixbuf o) => o -> m ()
clearCellRendererPixbufIconName :: o -> m ()
clearCellRendererPixbufIconName obj :: o
obj = IO () -> m ()
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 "icon-name" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)
#if defined(ENABLE_OVERLOADING)
data CellRendererPixbufIconNamePropertyInfo
instance AttrInfo CellRendererPixbufIconNamePropertyInfo where
type AttrAllowedOps CellRendererPixbufIconNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint CellRendererPixbufIconNamePropertyInfo = IsCellRendererPixbuf
type AttrSetTypeConstraint CellRendererPixbufIconNamePropertyInfo = (~) T.Text
type AttrTransferTypeConstraint CellRendererPixbufIconNamePropertyInfo = (~) T.Text
type AttrTransferType CellRendererPixbufIconNamePropertyInfo = T.Text
type AttrGetType CellRendererPixbufIconNamePropertyInfo = (Maybe T.Text)
type AttrLabel CellRendererPixbufIconNamePropertyInfo = "icon-name"
type AttrOrigin CellRendererPixbufIconNamePropertyInfo = CellRendererPixbuf
attrGet = getCellRendererPixbufIconName
attrSet = setCellRendererPixbufIconName
attrTransfer _ v = do
return v
attrConstruct = constructCellRendererPixbufIconName
attrClear = clearCellRendererPixbufIconName
#endif
getCellRendererPixbufPixbuf :: (MonadIO m, IsCellRendererPixbuf o) => o -> m (Maybe GdkPixbuf.Pixbuf.Pixbuf)
getCellRendererPixbufPixbuf :: o -> m (Maybe Pixbuf)
getCellRendererPixbufPixbuf obj :: o
obj = 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
$ o -> String -> (ManagedPtr Pixbuf -> Pixbuf) -> IO (Maybe Pixbuf)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj "pixbuf" ManagedPtr Pixbuf -> Pixbuf
GdkPixbuf.Pixbuf.Pixbuf
setCellRendererPixbufPixbuf :: (MonadIO m, IsCellRendererPixbuf o, GdkPixbuf.Pixbuf.IsPixbuf a) => o -> a -> m ()
setCellRendererPixbufPixbuf :: o -> a -> m ()
setCellRendererPixbufPixbuf obj :: o
obj val :: a
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj "pixbuf" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructCellRendererPixbufPixbuf :: (IsCellRendererPixbuf o, GdkPixbuf.Pixbuf.IsPixbuf a) => a -> IO (GValueConstruct o)
constructCellRendererPixbufPixbuf :: a -> IO (GValueConstruct o)
constructCellRendererPixbufPixbuf val :: a
val = String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject "pixbuf" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
clearCellRendererPixbufPixbuf :: (MonadIO m, IsCellRendererPixbuf o) => o -> m ()
clearCellRendererPixbufPixbuf :: o -> m ()
clearCellRendererPixbufPixbuf obj :: o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Pixbuf -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj "pixbuf" (Maybe Pixbuf
forall a. Maybe a
Nothing :: Maybe GdkPixbuf.Pixbuf.Pixbuf)
#if defined(ENABLE_OVERLOADING)
data CellRendererPixbufPixbufPropertyInfo
instance AttrInfo CellRendererPixbufPixbufPropertyInfo where
type AttrAllowedOps CellRendererPixbufPixbufPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint CellRendererPixbufPixbufPropertyInfo = IsCellRendererPixbuf
type AttrSetTypeConstraint CellRendererPixbufPixbufPropertyInfo = GdkPixbuf.Pixbuf.IsPixbuf
type AttrTransferTypeConstraint CellRendererPixbufPixbufPropertyInfo = GdkPixbuf.Pixbuf.IsPixbuf
type AttrTransferType CellRendererPixbufPixbufPropertyInfo = GdkPixbuf.Pixbuf.Pixbuf
type AttrGetType CellRendererPixbufPixbufPropertyInfo = (Maybe GdkPixbuf.Pixbuf.Pixbuf)
type AttrLabel CellRendererPixbufPixbufPropertyInfo = "pixbuf"
type AttrOrigin CellRendererPixbufPixbufPropertyInfo = CellRendererPixbuf
attrGet = getCellRendererPixbufPixbuf
attrSet = setCellRendererPixbufPixbuf
attrTransfer _ v = do
unsafeCastTo GdkPixbuf.Pixbuf.Pixbuf v
attrConstruct = constructCellRendererPixbufPixbuf
attrClear = clearCellRendererPixbufPixbuf
#endif
getCellRendererPixbufPixbufExpanderClosed :: (MonadIO m, IsCellRendererPixbuf o) => o -> m (Maybe GdkPixbuf.Pixbuf.Pixbuf)
getCellRendererPixbufPixbufExpanderClosed :: o -> m (Maybe Pixbuf)
getCellRendererPixbufPixbufExpanderClosed obj :: o
obj = 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
$ o -> String -> (ManagedPtr Pixbuf -> Pixbuf) -> IO (Maybe Pixbuf)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj "pixbuf-expander-closed" ManagedPtr Pixbuf -> Pixbuf
GdkPixbuf.Pixbuf.Pixbuf
setCellRendererPixbufPixbufExpanderClosed :: (MonadIO m, IsCellRendererPixbuf o, GdkPixbuf.Pixbuf.IsPixbuf a) => o -> a -> m ()
setCellRendererPixbufPixbufExpanderClosed :: o -> a -> m ()
setCellRendererPixbufPixbufExpanderClosed obj :: o
obj val :: a
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj "pixbuf-expander-closed" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructCellRendererPixbufPixbufExpanderClosed :: (IsCellRendererPixbuf o, GdkPixbuf.Pixbuf.IsPixbuf a) => a -> IO (GValueConstruct o)
constructCellRendererPixbufPixbufExpanderClosed :: a -> IO (GValueConstruct o)
constructCellRendererPixbufPixbufExpanderClosed val :: a
val = String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject "pixbuf-expander-closed" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
clearCellRendererPixbufPixbufExpanderClosed :: (MonadIO m, IsCellRendererPixbuf o) => o -> m ()
clearCellRendererPixbufPixbufExpanderClosed :: o -> m ()
clearCellRendererPixbufPixbufExpanderClosed obj :: o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Pixbuf -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj "pixbuf-expander-closed" (Maybe Pixbuf
forall a. Maybe a
Nothing :: Maybe GdkPixbuf.Pixbuf.Pixbuf)
#if defined(ENABLE_OVERLOADING)
data CellRendererPixbufPixbufExpanderClosedPropertyInfo
instance AttrInfo CellRendererPixbufPixbufExpanderClosedPropertyInfo where
type AttrAllowedOps CellRendererPixbufPixbufExpanderClosedPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint CellRendererPixbufPixbufExpanderClosedPropertyInfo = IsCellRendererPixbuf
type AttrSetTypeConstraint CellRendererPixbufPixbufExpanderClosedPropertyInfo = GdkPixbuf.Pixbuf.IsPixbuf
type AttrTransferTypeConstraint CellRendererPixbufPixbufExpanderClosedPropertyInfo = GdkPixbuf.Pixbuf.IsPixbuf
type AttrTransferType CellRendererPixbufPixbufExpanderClosedPropertyInfo = GdkPixbuf.Pixbuf.Pixbuf
type AttrGetType CellRendererPixbufPixbufExpanderClosedPropertyInfo = (Maybe GdkPixbuf.Pixbuf.Pixbuf)
type AttrLabel CellRendererPixbufPixbufExpanderClosedPropertyInfo = "pixbuf-expander-closed"
type AttrOrigin CellRendererPixbufPixbufExpanderClosedPropertyInfo = CellRendererPixbuf
attrGet = getCellRendererPixbufPixbufExpanderClosed
attrSet = setCellRendererPixbufPixbufExpanderClosed
attrTransfer _ v = do
unsafeCastTo GdkPixbuf.Pixbuf.Pixbuf v
attrConstruct = constructCellRendererPixbufPixbufExpanderClosed
attrClear = clearCellRendererPixbufPixbufExpanderClosed
#endif
getCellRendererPixbufPixbufExpanderOpen :: (MonadIO m, IsCellRendererPixbuf o) => o -> m (Maybe GdkPixbuf.Pixbuf.Pixbuf)
getCellRendererPixbufPixbufExpanderOpen :: o -> m (Maybe Pixbuf)
getCellRendererPixbufPixbufExpanderOpen obj :: o
obj = 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
$ o -> String -> (ManagedPtr Pixbuf -> Pixbuf) -> IO (Maybe Pixbuf)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj "pixbuf-expander-open" ManagedPtr Pixbuf -> Pixbuf
GdkPixbuf.Pixbuf.Pixbuf
setCellRendererPixbufPixbufExpanderOpen :: (MonadIO m, IsCellRendererPixbuf o, GdkPixbuf.Pixbuf.IsPixbuf a) => o -> a -> m ()
setCellRendererPixbufPixbufExpanderOpen :: o -> a -> m ()
setCellRendererPixbufPixbufExpanderOpen obj :: o
obj val :: a
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj "pixbuf-expander-open" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructCellRendererPixbufPixbufExpanderOpen :: (IsCellRendererPixbuf o, GdkPixbuf.Pixbuf.IsPixbuf a) => a -> IO (GValueConstruct o)
constructCellRendererPixbufPixbufExpanderOpen :: a -> IO (GValueConstruct o)
constructCellRendererPixbufPixbufExpanderOpen val :: a
val = String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject "pixbuf-expander-open" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
clearCellRendererPixbufPixbufExpanderOpen :: (MonadIO m, IsCellRendererPixbuf o) => o -> m ()
clearCellRendererPixbufPixbufExpanderOpen :: o -> m ()
clearCellRendererPixbufPixbufExpanderOpen obj :: o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Pixbuf -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj "pixbuf-expander-open" (Maybe Pixbuf
forall a. Maybe a
Nothing :: Maybe GdkPixbuf.Pixbuf.Pixbuf)
#if defined(ENABLE_OVERLOADING)
data CellRendererPixbufPixbufExpanderOpenPropertyInfo
instance AttrInfo CellRendererPixbufPixbufExpanderOpenPropertyInfo where
type AttrAllowedOps CellRendererPixbufPixbufExpanderOpenPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint CellRendererPixbufPixbufExpanderOpenPropertyInfo = IsCellRendererPixbuf
type AttrSetTypeConstraint CellRendererPixbufPixbufExpanderOpenPropertyInfo = GdkPixbuf.Pixbuf.IsPixbuf
type AttrTransferTypeConstraint CellRendererPixbufPixbufExpanderOpenPropertyInfo = GdkPixbuf.Pixbuf.IsPixbuf
type AttrTransferType CellRendererPixbufPixbufExpanderOpenPropertyInfo = GdkPixbuf.Pixbuf.Pixbuf
type AttrGetType CellRendererPixbufPixbufExpanderOpenPropertyInfo = (Maybe GdkPixbuf.Pixbuf.Pixbuf)
type AttrLabel CellRendererPixbufPixbufExpanderOpenPropertyInfo = "pixbuf-expander-open"
type AttrOrigin CellRendererPixbufPixbufExpanderOpenPropertyInfo = CellRendererPixbuf
attrGet = getCellRendererPixbufPixbufExpanderOpen
attrSet = setCellRendererPixbufPixbufExpanderOpen
attrTransfer _ v = do
unsafeCastTo GdkPixbuf.Pixbuf.Pixbuf v
attrConstruct = constructCellRendererPixbufPixbufExpanderOpen
attrClear = clearCellRendererPixbufPixbufExpanderOpen
#endif
getCellRendererPixbufStockDetail :: (MonadIO m, IsCellRendererPixbuf o) => o -> m (Maybe T.Text)
getCellRendererPixbufStockDetail :: o -> m (Maybe Text)
getCellRendererPixbufStockDetail obj :: o
obj = 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
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj "stock-detail"
setCellRendererPixbufStockDetail :: (MonadIO m, IsCellRendererPixbuf o) => o -> T.Text -> m ()
setCellRendererPixbufStockDetail :: o -> Text -> m ()
setCellRendererPixbufStockDetail obj :: o
obj val :: Text
val = IO () -> m ()
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 "stock-detail" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructCellRendererPixbufStockDetail :: (IsCellRendererPixbuf o) => T.Text -> IO (GValueConstruct o)
constructCellRendererPixbufStockDetail :: Text -> IO (GValueConstruct o)
constructCellRendererPixbufStockDetail val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "stock-detail" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
clearCellRendererPixbufStockDetail :: (MonadIO m, IsCellRendererPixbuf o) => o -> m ()
clearCellRendererPixbufStockDetail :: o -> m ()
clearCellRendererPixbufStockDetail obj :: o
obj = IO () -> m ()
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 "stock-detail" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)
#if defined(ENABLE_OVERLOADING)
data CellRendererPixbufStockDetailPropertyInfo
instance AttrInfo CellRendererPixbufStockDetailPropertyInfo where
type AttrAllowedOps CellRendererPixbufStockDetailPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint CellRendererPixbufStockDetailPropertyInfo = IsCellRendererPixbuf
type AttrSetTypeConstraint CellRendererPixbufStockDetailPropertyInfo = (~) T.Text
type AttrTransferTypeConstraint CellRendererPixbufStockDetailPropertyInfo = (~) T.Text
type AttrTransferType CellRendererPixbufStockDetailPropertyInfo = T.Text
type AttrGetType CellRendererPixbufStockDetailPropertyInfo = (Maybe T.Text)
type AttrLabel CellRendererPixbufStockDetailPropertyInfo = "stock-detail"
type AttrOrigin CellRendererPixbufStockDetailPropertyInfo = CellRendererPixbuf
attrGet = getCellRendererPixbufStockDetail
attrSet = setCellRendererPixbufStockDetail
attrTransfer _ v = do
return v
attrConstruct = constructCellRendererPixbufStockDetail
attrClear = clearCellRendererPixbufStockDetail
#endif
getCellRendererPixbufStockId :: (MonadIO m, IsCellRendererPixbuf o) => o -> m (Maybe T.Text)
getCellRendererPixbufStockId :: o -> m (Maybe Text)
getCellRendererPixbufStockId obj :: o
obj = 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
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj "stock-id"
setCellRendererPixbufStockId :: (MonadIO m, IsCellRendererPixbuf o) => o -> T.Text -> m ()
setCellRendererPixbufStockId :: o -> Text -> m ()
setCellRendererPixbufStockId obj :: o
obj val :: Text
val = IO () -> m ()
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 "stock-id" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructCellRendererPixbufStockId :: (IsCellRendererPixbuf o) => T.Text -> IO (GValueConstruct o)
constructCellRendererPixbufStockId :: Text -> IO (GValueConstruct o)
constructCellRendererPixbufStockId val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "stock-id" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
clearCellRendererPixbufStockId :: (MonadIO m, IsCellRendererPixbuf o) => o -> m ()
clearCellRendererPixbufStockId :: o -> m ()
clearCellRendererPixbufStockId obj :: o
obj = IO () -> m ()
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 "stock-id" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)
#if defined(ENABLE_OVERLOADING)
data CellRendererPixbufStockIdPropertyInfo
instance AttrInfo CellRendererPixbufStockIdPropertyInfo where
type AttrAllowedOps CellRendererPixbufStockIdPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint CellRendererPixbufStockIdPropertyInfo = IsCellRendererPixbuf
type AttrSetTypeConstraint CellRendererPixbufStockIdPropertyInfo = (~) T.Text
type AttrTransferTypeConstraint CellRendererPixbufStockIdPropertyInfo = (~) T.Text
type AttrTransferType CellRendererPixbufStockIdPropertyInfo = T.Text
type AttrGetType CellRendererPixbufStockIdPropertyInfo = (Maybe T.Text)
type AttrLabel CellRendererPixbufStockIdPropertyInfo = "stock-id"
type AttrOrigin CellRendererPixbufStockIdPropertyInfo = CellRendererPixbuf
attrGet = getCellRendererPixbufStockId
attrSet = setCellRendererPixbufStockId
attrTransfer _ v = do
return v
attrConstruct = constructCellRendererPixbufStockId
attrClear = clearCellRendererPixbufStockId
#endif
getCellRendererPixbufStockSize :: (MonadIO m, IsCellRendererPixbuf o) => o -> m Word32
getCellRendererPixbufStockSize :: o -> m Word32
getCellRendererPixbufStockSize obj :: o
obj = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj "stock-size"
setCellRendererPixbufStockSize :: (MonadIO m, IsCellRendererPixbuf o) => o -> Word32 -> m ()
setCellRendererPixbufStockSize :: o -> Word32 -> m ()
setCellRendererPixbufStockSize obj :: o
obj val :: Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Word32 -> IO ()
forall a. GObject a => a -> String -> Word32 -> IO ()
B.Properties.setObjectPropertyUInt32 o
obj "stock-size" Word32
val
constructCellRendererPixbufStockSize :: (IsCellRendererPixbuf o) => Word32 -> IO (GValueConstruct o)
constructCellRendererPixbufStockSize :: Word32 -> IO (GValueConstruct o)
constructCellRendererPixbufStockSize val :: Word32
val = String -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 "stock-size" Word32
val
#if defined(ENABLE_OVERLOADING)
data CellRendererPixbufStockSizePropertyInfo
instance AttrInfo CellRendererPixbufStockSizePropertyInfo where
type AttrAllowedOps CellRendererPixbufStockSizePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint CellRendererPixbufStockSizePropertyInfo = IsCellRendererPixbuf
type AttrSetTypeConstraint CellRendererPixbufStockSizePropertyInfo = (~) Word32
type AttrTransferTypeConstraint CellRendererPixbufStockSizePropertyInfo = (~) Word32
type AttrTransferType CellRendererPixbufStockSizePropertyInfo = Word32
type AttrGetType CellRendererPixbufStockSizePropertyInfo = Word32
type AttrLabel CellRendererPixbufStockSizePropertyInfo = "stock-size"
type AttrOrigin CellRendererPixbufStockSizePropertyInfo = CellRendererPixbuf
attrGet = getCellRendererPixbufStockSize
attrSet = setCellRendererPixbufStockSize
attrTransfer _ v = do
return v
attrConstruct = constructCellRendererPixbufStockSize
attrClear = undefined
#endif
getCellRendererPixbufSurface :: (MonadIO m, IsCellRendererPixbuf o) => o -> m (Maybe Cairo.Surface.Surface)
getCellRendererPixbufSurface :: o -> m (Maybe Surface)
getCellRendererPixbufSurface obj :: o
obj = 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
$ o
-> String -> (ManagedPtr Surface -> Surface) -> IO (Maybe Surface)
forall a b.
(GObject a, BoxedObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyBoxed o
obj "surface" ManagedPtr Surface -> Surface
Cairo.Surface.Surface
setCellRendererPixbufSurface :: (MonadIO m, IsCellRendererPixbuf o) => o -> Cairo.Surface.Surface -> m ()
setCellRendererPixbufSurface :: o -> Surface -> m ()
setCellRendererPixbufSurface obj :: o
obj val :: Surface
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Surface -> IO ()
forall a b.
(GObject a, BoxedObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyBoxed o
obj "surface" (Surface -> Maybe Surface
forall a. a -> Maybe a
Just Surface
val)
constructCellRendererPixbufSurface :: (IsCellRendererPixbuf o) => Cairo.Surface.Surface -> IO (GValueConstruct o)
constructCellRendererPixbufSurface :: Surface -> IO (GValueConstruct o)
constructCellRendererPixbufSurface val :: Surface
val = String -> Maybe Surface -> IO (GValueConstruct o)
forall a o.
BoxedObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBoxed "surface" (Surface -> Maybe Surface
forall a. a -> Maybe a
Just Surface
val)
clearCellRendererPixbufSurface :: (MonadIO m, IsCellRendererPixbuf o) => o -> m ()
clearCellRendererPixbufSurface :: o -> m ()
clearCellRendererPixbufSurface obj :: o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Surface -> IO ()
forall a b.
(GObject a, BoxedObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyBoxed o
obj "surface" (Maybe Surface
forall a. Maybe a
Nothing :: Maybe Cairo.Surface.Surface)
#if defined(ENABLE_OVERLOADING)
data CellRendererPixbufSurfacePropertyInfo
instance AttrInfo CellRendererPixbufSurfacePropertyInfo where
type AttrAllowedOps CellRendererPixbufSurfacePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint CellRendererPixbufSurfacePropertyInfo = IsCellRendererPixbuf
type AttrSetTypeConstraint CellRendererPixbufSurfacePropertyInfo = (~) Cairo.Surface.Surface
type AttrTransferTypeConstraint CellRendererPixbufSurfacePropertyInfo = (~) Cairo.Surface.Surface
type AttrTransferType CellRendererPixbufSurfacePropertyInfo = Cairo.Surface.Surface
type AttrGetType CellRendererPixbufSurfacePropertyInfo = (Maybe Cairo.Surface.Surface)
type AttrLabel CellRendererPixbufSurfacePropertyInfo = "surface"
type AttrOrigin CellRendererPixbufSurfacePropertyInfo = CellRendererPixbuf
attrGet = getCellRendererPixbufSurface
attrSet = setCellRendererPixbufSurface
attrTransfer _ v = do
return v
attrConstruct = constructCellRendererPixbufSurface
attrClear = clearCellRendererPixbufSurface
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList CellRendererPixbuf
type instance O.AttributeList CellRendererPixbuf = CellRendererPixbufAttributeList
type CellRendererPixbufAttributeList = ('[ '("cellBackground", Gtk.CellRenderer.CellRendererCellBackgroundPropertyInfo), '("cellBackgroundGdk", Gtk.CellRenderer.CellRendererCellBackgroundGdkPropertyInfo), '("cellBackgroundRgba", Gtk.CellRenderer.CellRendererCellBackgroundRgbaPropertyInfo), '("cellBackgroundSet", Gtk.CellRenderer.CellRendererCellBackgroundSetPropertyInfo), '("editing", Gtk.CellRenderer.CellRendererEditingPropertyInfo), '("followState", CellRendererPixbufFollowStatePropertyInfo), '("gicon", CellRendererPixbufGiconPropertyInfo), '("height", Gtk.CellRenderer.CellRendererHeightPropertyInfo), '("iconName", CellRendererPixbufIconNamePropertyInfo), '("isExpanded", Gtk.CellRenderer.CellRendererIsExpandedPropertyInfo), '("isExpander", Gtk.CellRenderer.CellRendererIsExpanderPropertyInfo), '("mode", Gtk.CellRenderer.CellRendererModePropertyInfo), '("pixbuf", CellRendererPixbufPixbufPropertyInfo), '("pixbufExpanderClosed", CellRendererPixbufPixbufExpanderClosedPropertyInfo), '("pixbufExpanderOpen", CellRendererPixbufPixbufExpanderOpenPropertyInfo), '("sensitive", Gtk.CellRenderer.CellRendererSensitivePropertyInfo), '("stockDetail", CellRendererPixbufStockDetailPropertyInfo), '("stockId", CellRendererPixbufStockIdPropertyInfo), '("stockSize", CellRendererPixbufStockSizePropertyInfo), '("surface", CellRendererPixbufSurfacePropertyInfo), '("visible", Gtk.CellRenderer.CellRendererVisiblePropertyInfo), '("width", Gtk.CellRenderer.CellRendererWidthPropertyInfo), '("xalign", Gtk.CellRenderer.CellRendererXalignPropertyInfo), '("xpad", Gtk.CellRenderer.CellRendererXpadPropertyInfo), '("yalign", Gtk.CellRenderer.CellRendererYalignPropertyInfo), '("ypad", Gtk.CellRenderer.CellRendererYpadPropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
cellRendererPixbufFollowState :: AttrLabelProxy "followState"
cellRendererPixbufFollowState = AttrLabelProxy
cellRendererPixbufGicon :: AttrLabelProxy "gicon"
cellRendererPixbufGicon = AttrLabelProxy
cellRendererPixbufIconName :: AttrLabelProxy "iconName"
cellRendererPixbufIconName = AttrLabelProxy
cellRendererPixbufPixbuf :: AttrLabelProxy "pixbuf"
cellRendererPixbufPixbuf = AttrLabelProxy
cellRendererPixbufPixbufExpanderClosed :: AttrLabelProxy "pixbufExpanderClosed"
cellRendererPixbufPixbufExpanderClosed = AttrLabelProxy
cellRendererPixbufPixbufExpanderOpen :: AttrLabelProxy "pixbufExpanderOpen"
cellRendererPixbufPixbufExpanderOpen = AttrLabelProxy
cellRendererPixbufStockDetail :: AttrLabelProxy "stockDetail"
cellRendererPixbufStockDetail = AttrLabelProxy
cellRendererPixbufStockId :: AttrLabelProxy "stockId"
cellRendererPixbufStockId = AttrLabelProxy
cellRendererPixbufStockSize :: AttrLabelProxy "stockSize"
cellRendererPixbufStockSize = AttrLabelProxy
cellRendererPixbufSurface :: AttrLabelProxy "surface"
cellRendererPixbufSurface = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList CellRendererPixbuf = CellRendererPixbufSignalList
type CellRendererPixbufSignalList = ('[ '("editingCanceled", Gtk.CellRenderer.CellRendererEditingCanceledSignalInfo), '("editingStarted", Gtk.CellRenderer.CellRendererEditingStartedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "gtk_cell_renderer_pixbuf_new" gtk_cell_renderer_pixbuf_new ::
IO (Ptr CellRendererPixbuf)
cellRendererPixbufNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
m CellRendererPixbuf
cellRendererPixbufNew :: m CellRendererPixbuf
cellRendererPixbufNew = IO CellRendererPixbuf -> m CellRendererPixbuf
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CellRendererPixbuf -> m CellRendererPixbuf)
-> IO CellRendererPixbuf -> m CellRendererPixbuf
forall a b. (a -> b) -> a -> b
$ do
Ptr CellRendererPixbuf
result <- IO (Ptr CellRendererPixbuf)
gtk_cell_renderer_pixbuf_new
Text -> Ptr CellRendererPixbuf -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "cellRendererPixbufNew" Ptr CellRendererPixbuf
result
CellRendererPixbuf
result' <- ((ManagedPtr CellRendererPixbuf -> CellRendererPixbuf)
-> Ptr CellRendererPixbuf -> IO CellRendererPixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr CellRendererPixbuf -> CellRendererPixbuf
CellRendererPixbuf) Ptr CellRendererPixbuf
result
CellRendererPixbuf -> IO CellRendererPixbuf
forall (m :: * -> *) a. Monad m => a -> m a
return CellRendererPixbuf
result'
#if defined(ENABLE_OVERLOADING)
#endif