{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.GtkSource.Objects.GutterRendererPixbuf
    ( 

-- * Exported types
    GutterRendererPixbuf(..)                ,
    IsGutterRendererPixbuf                  ,
    toGutterRendererPixbuf                  ,
    noGutterRendererPixbuf                  ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveGutterRendererPixbufMethod       ,
#endif


-- ** getGicon #method:getGicon#

#if defined(ENABLE_OVERLOADING)
    GutterRendererPixbufGetGiconMethodInfo  ,
#endif
    gutterRendererPixbufGetGicon            ,


-- ** getIconName #method:getIconName#

#if defined(ENABLE_OVERLOADING)
    GutterRendererPixbufGetIconNameMethodInfo,
#endif
    gutterRendererPixbufGetIconName         ,


-- ** getPixbuf #method:getPixbuf#

#if defined(ENABLE_OVERLOADING)
    GutterRendererPixbufGetPixbufMethodInfo ,
#endif
    gutterRendererPixbufGetPixbuf           ,


-- ** getStockId #method:getStockId#

#if defined(ENABLE_OVERLOADING)
    GutterRendererPixbufGetStockIdMethodInfo,
#endif
    gutterRendererPixbufGetStockId          ,


-- ** new #method:new#

    gutterRendererPixbufNew                 ,


-- ** setGicon #method:setGicon#

#if defined(ENABLE_OVERLOADING)
    GutterRendererPixbufSetGiconMethodInfo  ,
#endif
    gutterRendererPixbufSetGicon            ,


-- ** setIconName #method:setIconName#

#if defined(ENABLE_OVERLOADING)
    GutterRendererPixbufSetIconNameMethodInfo,
#endif
    gutterRendererPixbufSetIconName         ,


-- ** setPixbuf #method:setPixbuf#

#if defined(ENABLE_OVERLOADING)
    GutterRendererPixbufSetPixbufMethodInfo ,
#endif
    gutterRendererPixbufSetPixbuf           ,


-- ** setStockId #method:setStockId#

#if defined(ENABLE_OVERLOADING)
    GutterRendererPixbufSetStockIdMethodInfo,
#endif
    gutterRendererPixbufSetStockId          ,




 -- * Properties
-- ** gicon #attr:gicon#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    GutterRendererPixbufGiconPropertyInfo   ,
#endif
    clearGutterRendererPixbufGicon          ,
    constructGutterRendererPixbufGicon      ,
    getGutterRendererPixbufGicon            ,
#if defined(ENABLE_OVERLOADING)
    gutterRendererPixbufGicon               ,
#endif
    setGutterRendererPixbufGicon            ,


-- ** iconName #attr:iconName#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    GutterRendererPixbufIconNamePropertyInfo,
#endif
    clearGutterRendererPixbufIconName       ,
    constructGutterRendererPixbufIconName   ,
    getGutterRendererPixbufIconName         ,
#if defined(ENABLE_OVERLOADING)
    gutterRendererPixbufIconName            ,
#endif
    setGutterRendererPixbufIconName         ,


-- ** pixbuf #attr:pixbuf#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    GutterRendererPixbufPixbufPropertyInfo  ,
#endif
    clearGutterRendererPixbufPixbuf         ,
    constructGutterRendererPixbufPixbuf     ,
    getGutterRendererPixbufPixbuf           ,
#if defined(ENABLE_OVERLOADING)
    gutterRendererPixbufPixbuf              ,
#endif
    setGutterRendererPixbufPixbuf           ,


-- ** stockId #attr:stockId#
-- | The stock id.

#if defined(ENABLE_OVERLOADING)
    GutterRendererPixbufStockIdPropertyInfo ,
#endif
    clearGutterRendererPixbufStockId        ,
    constructGutterRendererPixbufStockId    ,
    getGutterRendererPixbufStockId          ,
#if defined(ENABLE_OVERLOADING)
    gutterRendererPixbufStockId             ,
#endif
    setGutterRendererPixbufStockId          ,




    ) 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.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.GtkSource.Objects.GutterRenderer as GtkSource.GutterRenderer

-- | Memory-managed wrapper type.
newtype GutterRendererPixbuf = GutterRendererPixbuf (ManagedPtr GutterRendererPixbuf)
    deriving (GutterRendererPixbuf -> GutterRendererPixbuf -> Bool
(GutterRendererPixbuf -> GutterRendererPixbuf -> Bool)
-> (GutterRendererPixbuf -> GutterRendererPixbuf -> Bool)
-> Eq GutterRendererPixbuf
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GutterRendererPixbuf -> GutterRendererPixbuf -> Bool
$c/= :: GutterRendererPixbuf -> GutterRendererPixbuf -> Bool
== :: GutterRendererPixbuf -> GutterRendererPixbuf -> Bool
$c== :: GutterRendererPixbuf -> GutterRendererPixbuf -> Bool
Eq)
foreign import ccall "gtk_source_gutter_renderer_pixbuf_get_type"
    c_gtk_source_gutter_renderer_pixbuf_get_type :: IO GType

instance GObject GutterRendererPixbuf where
    gobjectType :: IO GType
gobjectType = IO GType
c_gtk_source_gutter_renderer_pixbuf_get_type
    

-- | Convert 'GutterRendererPixbuf' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue GutterRendererPixbuf where
    toGValue :: GutterRendererPixbuf -> IO GValue
toGValue o :: GutterRendererPixbuf
o = do
        GType
gtype <- IO GType
c_gtk_source_gutter_renderer_pixbuf_get_type
        GutterRendererPixbuf
-> (Ptr GutterRendererPixbuf -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr GutterRendererPixbuf
o (GType
-> (GValue -> Ptr GutterRendererPixbuf -> IO ())
-> Ptr GutterRendererPixbuf
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr GutterRendererPixbuf -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO GutterRendererPixbuf
fromGValue gv :: GValue
gv = do
        Ptr GutterRendererPixbuf
ptr <- GValue -> IO (Ptr GutterRendererPixbuf)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr GutterRendererPixbuf)
        (ManagedPtr GutterRendererPixbuf -> GutterRendererPixbuf)
-> Ptr GutterRendererPixbuf -> IO GutterRendererPixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr GutterRendererPixbuf -> GutterRendererPixbuf
GutterRendererPixbuf Ptr GutterRendererPixbuf
ptr
        
    

-- | Type class for types which can be safely cast to `GutterRendererPixbuf`, for instance with `toGutterRendererPixbuf`.
class (GObject o, O.IsDescendantOf GutterRendererPixbuf o) => IsGutterRendererPixbuf o
instance (GObject o, O.IsDescendantOf GutterRendererPixbuf o) => IsGutterRendererPixbuf o

instance O.HasParentTypes GutterRendererPixbuf
type instance O.ParentTypes GutterRendererPixbuf = '[GtkSource.GutterRenderer.GutterRenderer, GObject.Object.Object]

-- | Cast to `GutterRendererPixbuf`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toGutterRendererPixbuf :: (MonadIO m, IsGutterRendererPixbuf o) => o -> m GutterRendererPixbuf
toGutterRendererPixbuf :: o -> m GutterRendererPixbuf
toGutterRendererPixbuf = IO GutterRendererPixbuf -> m GutterRendererPixbuf
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GutterRendererPixbuf -> m GutterRendererPixbuf)
-> (o -> IO GutterRendererPixbuf) -> o -> m GutterRendererPixbuf
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr GutterRendererPixbuf -> GutterRendererPixbuf)
-> o -> IO GutterRendererPixbuf
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr GutterRendererPixbuf -> GutterRendererPixbuf
GutterRendererPixbuf

-- | A convenience alias for `Nothing` :: `Maybe` `GutterRendererPixbuf`.
noGutterRendererPixbuf :: Maybe GutterRendererPixbuf
noGutterRendererPixbuf :: Maybe GutterRendererPixbuf
noGutterRendererPixbuf = Maybe GutterRendererPixbuf
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveGutterRendererPixbufMethod (t :: Symbol) (o :: *) :: * where
    ResolveGutterRendererPixbufMethod "activate" o = GtkSource.GutterRenderer.GutterRendererActivateMethodInfo
    ResolveGutterRendererPixbufMethod "begin" o = GtkSource.GutterRenderer.GutterRendererBeginMethodInfo
    ResolveGutterRendererPixbufMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveGutterRendererPixbufMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveGutterRendererPixbufMethod "draw" o = GtkSource.GutterRenderer.GutterRendererDrawMethodInfo
    ResolveGutterRendererPixbufMethod "end" o = GtkSource.GutterRenderer.GutterRendererEndMethodInfo
    ResolveGutterRendererPixbufMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveGutterRendererPixbufMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveGutterRendererPixbufMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveGutterRendererPixbufMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveGutterRendererPixbufMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveGutterRendererPixbufMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveGutterRendererPixbufMethod "queryActivatable" o = GtkSource.GutterRenderer.GutterRendererQueryActivatableMethodInfo
    ResolveGutterRendererPixbufMethod "queryData" o = GtkSource.GutterRenderer.GutterRendererQueryDataMethodInfo
    ResolveGutterRendererPixbufMethod "queryTooltip" o = GtkSource.GutterRenderer.GutterRendererQueryTooltipMethodInfo
    ResolveGutterRendererPixbufMethod "queueDraw" o = GtkSource.GutterRenderer.GutterRendererQueueDrawMethodInfo
    ResolveGutterRendererPixbufMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveGutterRendererPixbufMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveGutterRendererPixbufMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveGutterRendererPixbufMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveGutterRendererPixbufMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveGutterRendererPixbufMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveGutterRendererPixbufMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveGutterRendererPixbufMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveGutterRendererPixbufMethod "getAlignment" o = GtkSource.GutterRenderer.GutterRendererGetAlignmentMethodInfo
    ResolveGutterRendererPixbufMethod "getAlignmentMode" o = GtkSource.GutterRenderer.GutterRendererGetAlignmentModeMethodInfo
    ResolveGutterRendererPixbufMethod "getBackground" o = GtkSource.GutterRenderer.GutterRendererGetBackgroundMethodInfo
    ResolveGutterRendererPixbufMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveGutterRendererPixbufMethod "getGicon" o = GutterRendererPixbufGetGiconMethodInfo
    ResolveGutterRendererPixbufMethod "getIconName" o = GutterRendererPixbufGetIconNameMethodInfo
    ResolveGutterRendererPixbufMethod "getPadding" o = GtkSource.GutterRenderer.GutterRendererGetPaddingMethodInfo
    ResolveGutterRendererPixbufMethod "getPixbuf" o = GutterRendererPixbufGetPixbufMethodInfo
    ResolveGutterRendererPixbufMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveGutterRendererPixbufMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveGutterRendererPixbufMethod "getSize" o = GtkSource.GutterRenderer.GutterRendererGetSizeMethodInfo
    ResolveGutterRendererPixbufMethod "getStockId" o = GutterRendererPixbufGetStockIdMethodInfo
    ResolveGutterRendererPixbufMethod "getView" o = GtkSource.GutterRenderer.GutterRendererGetViewMethodInfo
    ResolveGutterRendererPixbufMethod "getVisible" o = GtkSource.GutterRenderer.GutterRendererGetVisibleMethodInfo
    ResolveGutterRendererPixbufMethod "getWindowType" o = GtkSource.GutterRenderer.GutterRendererGetWindowTypeMethodInfo
    ResolveGutterRendererPixbufMethod "setAlignment" o = GtkSource.GutterRenderer.GutterRendererSetAlignmentMethodInfo
    ResolveGutterRendererPixbufMethod "setAlignmentMode" o = GtkSource.GutterRenderer.GutterRendererSetAlignmentModeMethodInfo
    ResolveGutterRendererPixbufMethod "setBackground" o = GtkSource.GutterRenderer.GutterRendererSetBackgroundMethodInfo
    ResolveGutterRendererPixbufMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveGutterRendererPixbufMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveGutterRendererPixbufMethod "setGicon" o = GutterRendererPixbufSetGiconMethodInfo
    ResolveGutterRendererPixbufMethod "setIconName" o = GutterRendererPixbufSetIconNameMethodInfo
    ResolveGutterRendererPixbufMethod "setPadding" o = GtkSource.GutterRenderer.GutterRendererSetPaddingMethodInfo
    ResolveGutterRendererPixbufMethod "setPixbuf" o = GutterRendererPixbufSetPixbufMethodInfo
    ResolveGutterRendererPixbufMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveGutterRendererPixbufMethod "setSize" o = GtkSource.GutterRenderer.GutterRendererSetSizeMethodInfo
    ResolveGutterRendererPixbufMethod "setStockId" o = GutterRendererPixbufSetStockIdMethodInfo
    ResolveGutterRendererPixbufMethod "setVisible" o = GtkSource.GutterRenderer.GutterRendererSetVisibleMethodInfo
    ResolveGutterRendererPixbufMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveGutterRendererPixbufMethod t GutterRendererPixbuf, O.MethodInfo info GutterRendererPixbuf p) => OL.IsLabel t (GutterRendererPixbuf -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif

-- VVV Prop "gicon"
   -- Type: TInterface (Name {namespace = "Gio", name = "Icon"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just True)

-- | Get the value of the “@gicon@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' gutterRendererPixbuf #gicon
-- @
getGutterRendererPixbufGicon :: (MonadIO m, IsGutterRendererPixbuf o) => o -> m Gio.Icon.Icon
getGutterRendererPixbufGicon :: o -> m Icon
getGutterRendererPixbufGicon obj :: o
obj = IO Icon -> m Icon
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
$ Text -> IO (Maybe Icon) -> IO Icon
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing "getGutterRendererPixbufGicon" (IO (Maybe Icon) -> IO Icon) -> IO (Maybe Icon) -> IO 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

-- | Set the value of the “@gicon@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' gutterRendererPixbuf [ #gicon 'Data.GI.Base.Attributes.:=' value ]
-- @
setGutterRendererPixbufGicon :: (MonadIO m, IsGutterRendererPixbuf o, Gio.Icon.IsIcon a) => o -> a -> m ()
setGutterRendererPixbufGicon :: o -> a -> m ()
setGutterRendererPixbufGicon 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)

-- | Construct a `GValueConstruct` with valid value for the “@gicon@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructGutterRendererPixbufGicon :: (IsGutterRendererPixbuf o, Gio.Icon.IsIcon a) => a -> IO (GValueConstruct o)
constructGutterRendererPixbufGicon :: a -> IO (GValueConstruct o)
constructGutterRendererPixbufGicon 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)

-- | Set the value of the “@gicon@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #gicon
-- @
clearGutterRendererPixbufGicon :: (MonadIO m, IsGutterRendererPixbuf o) => o -> m ()
clearGutterRendererPixbufGicon :: o -> m ()
clearGutterRendererPixbufGicon 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 GutterRendererPixbufGiconPropertyInfo
instance AttrInfo GutterRendererPixbufGiconPropertyInfo where
    type AttrAllowedOps GutterRendererPixbufGiconPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint GutterRendererPixbufGiconPropertyInfo = IsGutterRendererPixbuf
    type AttrSetTypeConstraint GutterRendererPixbufGiconPropertyInfo = Gio.Icon.IsIcon
    type AttrTransferTypeConstraint GutterRendererPixbufGiconPropertyInfo = Gio.Icon.IsIcon
    type AttrTransferType GutterRendererPixbufGiconPropertyInfo = Gio.Icon.Icon
    type AttrGetType GutterRendererPixbufGiconPropertyInfo = Gio.Icon.Icon
    type AttrLabel GutterRendererPixbufGiconPropertyInfo = "gicon"
    type AttrOrigin GutterRendererPixbufGiconPropertyInfo = GutterRendererPixbuf
    attrGet = getGutterRendererPixbufGicon
    attrSet = setGutterRendererPixbufGicon
    attrTransfer _ v = do
        unsafeCastTo Gio.Icon.Icon v
    attrConstruct = constructGutterRendererPixbufGicon
    attrClear = clearGutterRendererPixbufGicon
#endif

-- VVV Prop "icon-name"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just True)

-- | Get the value of the “@icon-name@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' gutterRendererPixbuf #iconName
-- @
getGutterRendererPixbufIconName :: (MonadIO m, IsGutterRendererPixbuf o) => o -> m T.Text
getGutterRendererPixbufIconName :: o -> m Text
getGutterRendererPixbufIconName obj :: o
obj = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing "getGutterRendererPixbufIconName" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO 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"

-- | Set the value of the “@icon-name@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' gutterRendererPixbuf [ #iconName 'Data.GI.Base.Attributes.:=' value ]
-- @
setGutterRendererPixbufIconName :: (MonadIO m, IsGutterRendererPixbuf o) => o -> T.Text -> m ()
setGutterRendererPixbufIconName :: o -> Text -> m ()
setGutterRendererPixbufIconName 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)

-- | Construct a `GValueConstruct` with valid value for the “@icon-name@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructGutterRendererPixbufIconName :: (IsGutterRendererPixbuf o) => T.Text -> IO (GValueConstruct o)
constructGutterRendererPixbufIconName :: Text -> IO (GValueConstruct o)
constructGutterRendererPixbufIconName 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)

-- | Set the value of the “@icon-name@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #iconName
-- @
clearGutterRendererPixbufIconName :: (MonadIO m, IsGutterRendererPixbuf o) => o -> m ()
clearGutterRendererPixbufIconName :: o -> m ()
clearGutterRendererPixbufIconName 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 GutterRendererPixbufIconNamePropertyInfo
instance AttrInfo GutterRendererPixbufIconNamePropertyInfo where
    type AttrAllowedOps GutterRendererPixbufIconNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint GutterRendererPixbufIconNamePropertyInfo = IsGutterRendererPixbuf
    type AttrSetTypeConstraint GutterRendererPixbufIconNamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint GutterRendererPixbufIconNamePropertyInfo = (~) T.Text
    type AttrTransferType GutterRendererPixbufIconNamePropertyInfo = T.Text
    type AttrGetType GutterRendererPixbufIconNamePropertyInfo = T.Text
    type AttrLabel GutterRendererPixbufIconNamePropertyInfo = "icon-name"
    type AttrOrigin GutterRendererPixbufIconNamePropertyInfo = GutterRendererPixbuf
    attrGet = getGutterRendererPixbufIconName
    attrSet = setGutterRendererPixbufIconName
    attrTransfer _ v = do
        return v
    attrConstruct = constructGutterRendererPixbufIconName
    attrClear = clearGutterRendererPixbufIconName
#endif

-- VVV Prop "pixbuf"
   -- Type: TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just True)

-- | Get the value of the “@pixbuf@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' gutterRendererPixbuf #pixbuf
-- @
getGutterRendererPixbufPixbuf :: (MonadIO m, IsGutterRendererPixbuf o) => o -> m GdkPixbuf.Pixbuf.Pixbuf
getGutterRendererPixbufPixbuf :: o -> m Pixbuf
getGutterRendererPixbufPixbuf obj :: o
obj = IO Pixbuf -> m Pixbuf
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Pixbuf -> m Pixbuf) -> IO Pixbuf -> m Pixbuf
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Pixbuf) -> IO Pixbuf
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing "getGutterRendererPixbufPixbuf" (IO (Maybe Pixbuf) -> IO Pixbuf) -> IO (Maybe Pixbuf) -> IO 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

-- | Set the value of the “@pixbuf@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' gutterRendererPixbuf [ #pixbuf 'Data.GI.Base.Attributes.:=' value ]
-- @
setGutterRendererPixbufPixbuf :: (MonadIO m, IsGutterRendererPixbuf o, GdkPixbuf.Pixbuf.IsPixbuf a) => o -> a -> m ()
setGutterRendererPixbufPixbuf :: o -> a -> m ()
setGutterRendererPixbufPixbuf 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)

-- | Construct a `GValueConstruct` with valid value for the “@pixbuf@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructGutterRendererPixbufPixbuf :: (IsGutterRendererPixbuf o, GdkPixbuf.Pixbuf.IsPixbuf a) => a -> IO (GValueConstruct o)
constructGutterRendererPixbufPixbuf :: a -> IO (GValueConstruct o)
constructGutterRendererPixbufPixbuf 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)

-- | Set the value of the “@pixbuf@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #pixbuf
-- @
clearGutterRendererPixbufPixbuf :: (MonadIO m, IsGutterRendererPixbuf o) => o -> m ()
clearGutterRendererPixbufPixbuf :: o -> m ()
clearGutterRendererPixbufPixbuf 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 GutterRendererPixbufPixbufPropertyInfo
instance AttrInfo GutterRendererPixbufPixbufPropertyInfo where
    type AttrAllowedOps GutterRendererPixbufPixbufPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint GutterRendererPixbufPixbufPropertyInfo = IsGutterRendererPixbuf
    type AttrSetTypeConstraint GutterRendererPixbufPixbufPropertyInfo = GdkPixbuf.Pixbuf.IsPixbuf
    type AttrTransferTypeConstraint GutterRendererPixbufPixbufPropertyInfo = GdkPixbuf.Pixbuf.IsPixbuf
    type AttrTransferType GutterRendererPixbufPixbufPropertyInfo = GdkPixbuf.Pixbuf.Pixbuf
    type AttrGetType GutterRendererPixbufPixbufPropertyInfo = GdkPixbuf.Pixbuf.Pixbuf
    type AttrLabel GutterRendererPixbufPixbufPropertyInfo = "pixbuf"
    type AttrOrigin GutterRendererPixbufPixbufPropertyInfo = GutterRendererPixbuf
    attrGet = getGutterRendererPixbufPixbuf
    attrSet = setGutterRendererPixbufPixbuf
    attrTransfer _ v = do
        unsafeCastTo GdkPixbuf.Pixbuf.Pixbuf v
    attrConstruct = constructGutterRendererPixbufPixbuf
    attrClear = clearGutterRendererPixbufPixbuf
#endif

-- VVV Prop "stock-id"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just True)

-- | Get the value of the “@stock-id@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' gutterRendererPixbuf #stockId
-- @
getGutterRendererPixbufStockId :: (MonadIO m, IsGutterRendererPixbuf o) => o -> m T.Text
getGutterRendererPixbufStockId :: o -> m Text
getGutterRendererPixbufStockId obj :: o
obj = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing "getGutterRendererPixbufStockId" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO 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"

-- | Set the value of the “@stock-id@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' gutterRendererPixbuf [ #stockId 'Data.GI.Base.Attributes.:=' value ]
-- @
setGutterRendererPixbufStockId :: (MonadIO m, IsGutterRendererPixbuf o) => o -> T.Text -> m ()
setGutterRendererPixbufStockId :: o -> Text -> m ()
setGutterRendererPixbufStockId 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)

-- | Construct a `GValueConstruct` with valid value for the “@stock-id@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructGutterRendererPixbufStockId :: (IsGutterRendererPixbuf o) => T.Text -> IO (GValueConstruct o)
constructGutterRendererPixbufStockId :: Text -> IO (GValueConstruct o)
constructGutterRendererPixbufStockId 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)

-- | Set the value of the “@stock-id@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #stockId
-- @
clearGutterRendererPixbufStockId :: (MonadIO m, IsGutterRendererPixbuf o) => o -> m ()
clearGutterRendererPixbufStockId :: o -> m ()
clearGutterRendererPixbufStockId 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 GutterRendererPixbufStockIdPropertyInfo
instance AttrInfo GutterRendererPixbufStockIdPropertyInfo where
    type AttrAllowedOps GutterRendererPixbufStockIdPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint GutterRendererPixbufStockIdPropertyInfo = IsGutterRendererPixbuf
    type AttrSetTypeConstraint GutterRendererPixbufStockIdPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint GutterRendererPixbufStockIdPropertyInfo = (~) T.Text
    type AttrTransferType GutterRendererPixbufStockIdPropertyInfo = T.Text
    type AttrGetType GutterRendererPixbufStockIdPropertyInfo = T.Text
    type AttrLabel GutterRendererPixbufStockIdPropertyInfo = "stock-id"
    type AttrOrigin GutterRendererPixbufStockIdPropertyInfo = GutterRendererPixbuf
    attrGet = getGutterRendererPixbufStockId
    attrSet = setGutterRendererPixbufStockId
    attrTransfer _ v = do
        return v
    attrConstruct = constructGutterRendererPixbufStockId
    attrClear = clearGutterRendererPixbufStockId
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList GutterRendererPixbuf
type instance O.AttributeList GutterRendererPixbuf = GutterRendererPixbufAttributeList
type GutterRendererPixbufAttributeList = ('[ '("alignmentMode", GtkSource.GutterRenderer.GutterRendererAlignmentModePropertyInfo), '("backgroundRgba", GtkSource.GutterRenderer.GutterRendererBackgroundRgbaPropertyInfo), '("backgroundSet", GtkSource.GutterRenderer.GutterRendererBackgroundSetPropertyInfo), '("gicon", GutterRendererPixbufGiconPropertyInfo), '("iconName", GutterRendererPixbufIconNamePropertyInfo), '("pixbuf", GutterRendererPixbufPixbufPropertyInfo), '("size", GtkSource.GutterRenderer.GutterRendererSizePropertyInfo), '("stockId", GutterRendererPixbufStockIdPropertyInfo), '("view", GtkSource.GutterRenderer.GutterRendererViewPropertyInfo), '("visible", GtkSource.GutterRenderer.GutterRendererVisiblePropertyInfo), '("windowType", GtkSource.GutterRenderer.GutterRendererWindowTypePropertyInfo), '("xalign", GtkSource.GutterRenderer.GutterRendererXalignPropertyInfo), '("xpad", GtkSource.GutterRenderer.GutterRendererXpadPropertyInfo), '("yalign", GtkSource.GutterRenderer.GutterRendererYalignPropertyInfo), '("ypad", GtkSource.GutterRenderer.GutterRendererYpadPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
gutterRendererPixbufGicon :: AttrLabelProxy "gicon"
gutterRendererPixbufGicon = AttrLabelProxy

gutterRendererPixbufIconName :: AttrLabelProxy "iconName"
gutterRendererPixbufIconName = AttrLabelProxy

gutterRendererPixbufPixbuf :: AttrLabelProxy "pixbuf"
gutterRendererPixbufPixbuf = AttrLabelProxy

gutterRendererPixbufStockId :: AttrLabelProxy "stockId"
gutterRendererPixbufStockId = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList GutterRendererPixbuf = GutterRendererPixbufSignalList
type GutterRendererPixbufSignalList = ('[ '("activate", GtkSource.GutterRenderer.GutterRendererActivateSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("queryActivatable", GtkSource.GutterRenderer.GutterRendererQueryActivatableSignalInfo), '("queryData", GtkSource.GutterRenderer.GutterRendererQueryDataSignalInfo), '("queryTooltip", GtkSource.GutterRenderer.GutterRendererQueryTooltipSignalInfo), '("queueDraw", GtkSource.GutterRenderer.GutterRendererQueueDrawSignalInfo)] :: [(Symbol, *)])

#endif

-- method GutterRendererPixbuf::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "GtkSource" , name = "GutterRendererPixbuf" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_source_gutter_renderer_pixbuf_new" gtk_source_gutter_renderer_pixbuf_new :: 
    IO (Ptr GutterRendererPixbuf)

-- | Create a new t'GI.GtkSource.Objects.GutterRendererPixbuf.GutterRendererPixbuf'.
gutterRendererPixbufNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m GutterRendererPixbuf
    -- ^ __Returns:__ A t'GI.GtkSource.Objects.GutterRenderer.GutterRenderer'
gutterRendererPixbufNew :: m GutterRendererPixbuf
gutterRendererPixbufNew  = IO GutterRendererPixbuf -> m GutterRendererPixbuf
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GutterRendererPixbuf -> m GutterRendererPixbuf)
-> IO GutterRendererPixbuf -> m GutterRendererPixbuf
forall a b. (a -> b) -> a -> b
$ do
    Ptr GutterRendererPixbuf
result <- IO (Ptr GutterRendererPixbuf)
gtk_source_gutter_renderer_pixbuf_new
    Text -> Ptr GutterRendererPixbuf -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "gutterRendererPixbufNew" Ptr GutterRendererPixbuf
result
    GutterRendererPixbuf
result' <- ((ManagedPtr GutterRendererPixbuf -> GutterRendererPixbuf)
-> Ptr GutterRendererPixbuf -> IO GutterRendererPixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr GutterRendererPixbuf -> GutterRendererPixbuf
GutterRendererPixbuf) Ptr GutterRendererPixbuf
result
    GutterRendererPixbuf -> IO GutterRendererPixbuf
forall (m :: * -> *) a. Monad m => a -> m a
return GutterRendererPixbuf
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method GutterRendererPixbuf::get_gicon
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "renderer"
--           , argType =
--               TInterface
--                 Name { namespace = "GtkSource" , name = "GutterRendererPixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkSourceGutterRendererPixbuf"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "Icon" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_source_gutter_renderer_pixbuf_get_gicon" gtk_source_gutter_renderer_pixbuf_get_gicon :: 
    Ptr GutterRendererPixbuf ->             -- renderer : TInterface (Name {namespace = "GtkSource", name = "GutterRendererPixbuf"})
    IO (Ptr Gio.Icon.Icon)

-- | Get the gicon of the renderer
gutterRendererPixbufGetGicon ::
    (B.CallStack.HasCallStack, MonadIO m, IsGutterRendererPixbuf a) =>
    a
    -- ^ /@renderer@/: a t'GI.GtkSource.Objects.GutterRendererPixbuf.GutterRendererPixbuf'
    -> m Gio.Icon.Icon
    -- ^ __Returns:__ a t'GI.Gio.Interfaces.Icon.Icon'
gutterRendererPixbufGetGicon :: a -> m Icon
gutterRendererPixbufGetGicon renderer :: a
renderer = IO Icon -> m Icon
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 GutterRendererPixbuf
renderer' <- a -> IO (Ptr GutterRendererPixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
renderer
    Ptr Icon
result <- Ptr GutterRendererPixbuf -> IO (Ptr Icon)
gtk_source_gutter_renderer_pixbuf_get_gicon Ptr GutterRendererPixbuf
renderer'
    Text -> Ptr Icon -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "gutterRendererPixbufGetGicon" 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
newObject ManagedPtr Icon -> Icon
Gio.Icon.Icon) Ptr Icon
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
renderer
    Icon -> IO Icon
forall (m :: * -> *) a. Monad m => a -> m a
return Icon
result'

#if defined(ENABLE_OVERLOADING)
data GutterRendererPixbufGetGiconMethodInfo
instance (signature ~ (m Gio.Icon.Icon), MonadIO m, IsGutterRendererPixbuf a) => O.MethodInfo GutterRendererPixbufGetGiconMethodInfo a signature where
    overloadedMethod = gutterRendererPixbufGetGicon

#endif

-- method GutterRendererPixbuf::get_icon_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "renderer"
--           , argType =
--               TInterface
--                 Name { namespace = "GtkSource" , name = "GutterRendererPixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_source_gutter_renderer_pixbuf_get_icon_name" gtk_source_gutter_renderer_pixbuf_get_icon_name :: 
    Ptr GutterRendererPixbuf ->             -- renderer : TInterface (Name {namespace = "GtkSource", name = "GutterRendererPixbuf"})
    IO CString

-- | /No description available in the introspection data./
gutterRendererPixbufGetIconName ::
    (B.CallStack.HasCallStack, MonadIO m, IsGutterRendererPixbuf a) =>
    a
    -> m T.Text
gutterRendererPixbufGetIconName :: a -> m Text
gutterRendererPixbufGetIconName renderer :: a
renderer = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr GutterRendererPixbuf
renderer' <- a -> IO (Ptr GutterRendererPixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
renderer
    CString
result <- Ptr GutterRendererPixbuf -> IO CString
gtk_source_gutter_renderer_pixbuf_get_icon_name Ptr GutterRendererPixbuf
renderer'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "gutterRendererPixbufGetIconName" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
renderer
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data GutterRendererPixbufGetIconNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsGutterRendererPixbuf a) => O.MethodInfo GutterRendererPixbufGetIconNameMethodInfo a signature where
    overloadedMethod = gutterRendererPixbufGetIconName

#endif

-- method GutterRendererPixbuf::get_pixbuf
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "renderer"
--           , argType =
--               TInterface
--                 Name { namespace = "GtkSource" , name = "GutterRendererPixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkSourceGutterRendererPixbuf"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_source_gutter_renderer_pixbuf_get_pixbuf" gtk_source_gutter_renderer_pixbuf_get_pixbuf :: 
    Ptr GutterRendererPixbuf ->             -- renderer : TInterface (Name {namespace = "GtkSource", name = "GutterRendererPixbuf"})
    IO (Ptr GdkPixbuf.Pixbuf.Pixbuf)

-- | Get the pixbuf of the renderer.
gutterRendererPixbufGetPixbuf ::
    (B.CallStack.HasCallStack, MonadIO m, IsGutterRendererPixbuf a) =>
    a
    -- ^ /@renderer@/: a t'GI.GtkSource.Objects.GutterRendererPixbuf.GutterRendererPixbuf'
    -> m GdkPixbuf.Pixbuf.Pixbuf
    -- ^ __Returns:__ a t'GI.GdkPixbuf.Objects.Pixbuf.Pixbuf'
gutterRendererPixbufGetPixbuf :: a -> m Pixbuf
gutterRendererPixbufGetPixbuf renderer :: a
renderer = IO Pixbuf -> m Pixbuf
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Pixbuf -> m Pixbuf) -> IO Pixbuf -> m Pixbuf
forall a b. (a -> b) -> a -> b
$ do
    Ptr GutterRendererPixbuf
renderer' <- a -> IO (Ptr GutterRendererPixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
renderer
    Ptr Pixbuf
result <- Ptr GutterRendererPixbuf -> IO (Ptr Pixbuf)
gtk_source_gutter_renderer_pixbuf_get_pixbuf Ptr GutterRendererPixbuf
renderer'
    Text -> Ptr Pixbuf -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "gutterRendererPixbufGetPixbuf" Ptr Pixbuf
result
    Pixbuf
result' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Pixbuf -> Pixbuf
GdkPixbuf.Pixbuf.Pixbuf) Ptr Pixbuf
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
renderer
    Pixbuf -> IO Pixbuf
forall (m :: * -> *) a. Monad m => a -> m a
return Pixbuf
result'

#if defined(ENABLE_OVERLOADING)
data GutterRendererPixbufGetPixbufMethodInfo
instance (signature ~ (m GdkPixbuf.Pixbuf.Pixbuf), MonadIO m, IsGutterRendererPixbuf a) => O.MethodInfo GutterRendererPixbufGetPixbufMethodInfo a signature where
    overloadedMethod = gutterRendererPixbufGetPixbuf

#endif

-- method GutterRendererPixbuf::get_stock_id
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "renderer"
--           , argType =
--               TInterface
--                 Name { namespace = "GtkSource" , name = "GutterRendererPixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkSourceGutterRendererPixbuf"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_source_gutter_renderer_pixbuf_get_stock_id" gtk_source_gutter_renderer_pixbuf_get_stock_id :: 
    Ptr GutterRendererPixbuf ->             -- renderer : TInterface (Name {namespace = "GtkSource", name = "GutterRendererPixbuf"})
    IO CString

{-# DEPRECATED gutterRendererPixbufGetStockId ["(Since version 3.10)","Don\\'t use this function."] #-}
-- | /No description available in the introspection data./
gutterRendererPixbufGetStockId ::
    (B.CallStack.HasCallStack, MonadIO m, IsGutterRendererPixbuf a) =>
    a
    -- ^ /@renderer@/: a t'GI.GtkSource.Objects.GutterRendererPixbuf.GutterRendererPixbuf'
    -> m T.Text
    -- ^ __Returns:__ the stock id.
gutterRendererPixbufGetStockId :: a -> m Text
gutterRendererPixbufGetStockId renderer :: a
renderer = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr GutterRendererPixbuf
renderer' <- a -> IO (Ptr GutterRendererPixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
renderer
    CString
result <- Ptr GutterRendererPixbuf -> IO CString
gtk_source_gutter_renderer_pixbuf_get_stock_id Ptr GutterRendererPixbuf
renderer'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "gutterRendererPixbufGetStockId" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
renderer
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data GutterRendererPixbufGetStockIdMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsGutterRendererPixbuf a) => O.MethodInfo GutterRendererPixbufGetStockIdMethodInfo a signature where
    overloadedMethod = gutterRendererPixbufGetStockId

#endif

-- method GutterRendererPixbuf::set_gicon
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "renderer"
--           , argType =
--               TInterface
--                 Name { namespace = "GtkSource" , name = "GutterRendererPixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkSourceGutterRendererPixbuf"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "icon"
--           , argType = TInterface Name { namespace = "Gio" , name = "Icon" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the icon, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_source_gutter_renderer_pixbuf_set_gicon" gtk_source_gutter_renderer_pixbuf_set_gicon :: 
    Ptr GutterRendererPixbuf ->             -- renderer : TInterface (Name {namespace = "GtkSource", name = "GutterRendererPixbuf"})
    Ptr Gio.Icon.Icon ->                    -- icon : TInterface (Name {namespace = "Gio", name = "Icon"})
    IO ()

-- | /No description available in the introspection data./
gutterRendererPixbufSetGicon ::
    (B.CallStack.HasCallStack, MonadIO m, IsGutterRendererPixbuf a, Gio.Icon.IsIcon b) =>
    a
    -- ^ /@renderer@/: a t'GI.GtkSource.Objects.GutterRendererPixbuf.GutterRendererPixbuf'
    -> Maybe (b)
    -- ^ /@icon@/: the icon, or 'P.Nothing'.
    -> m ()
gutterRendererPixbufSetGicon :: a -> Maybe b -> m ()
gutterRendererPixbufSetGicon renderer :: a
renderer icon :: Maybe b
icon = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr GutterRendererPixbuf
renderer' <- a -> IO (Ptr GutterRendererPixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
renderer
    Ptr Icon
maybeIcon <- case Maybe b
icon of
        Nothing -> Ptr Icon -> IO (Ptr Icon)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Icon
forall a. Ptr a
nullPtr
        Just jIcon :: 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 (m :: * -> *) a. Monad m => a -> m a
return Ptr Icon
jIcon'
    Ptr GutterRendererPixbuf -> Ptr Icon -> IO ()
gtk_source_gutter_renderer_pixbuf_set_gicon Ptr GutterRendererPixbuf
renderer' Ptr Icon
maybeIcon
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
renderer
    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 (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data GutterRendererPixbufSetGiconMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsGutterRendererPixbuf a, Gio.Icon.IsIcon b) => O.MethodInfo GutterRendererPixbufSetGiconMethodInfo a signature where
    overloadedMethod = gutterRendererPixbufSetGicon

#endif

-- method GutterRendererPixbuf::set_icon_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "renderer"
--           , argType =
--               TInterface
--                 Name { namespace = "GtkSource" , name = "GutterRendererPixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkSourceGutterRendererPixbuf"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "icon_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the icon name, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_source_gutter_renderer_pixbuf_set_icon_name" gtk_source_gutter_renderer_pixbuf_set_icon_name :: 
    Ptr GutterRendererPixbuf ->             -- renderer : TInterface (Name {namespace = "GtkSource", name = "GutterRendererPixbuf"})
    CString ->                              -- icon_name : TBasicType TUTF8
    IO ()

-- | /No description available in the introspection data./
gutterRendererPixbufSetIconName ::
    (B.CallStack.HasCallStack, MonadIO m, IsGutterRendererPixbuf a) =>
    a
    -- ^ /@renderer@/: a t'GI.GtkSource.Objects.GutterRendererPixbuf.GutterRendererPixbuf'
    -> Maybe (T.Text)
    -- ^ /@iconName@/: the icon name, or 'P.Nothing'.
    -> m ()
gutterRendererPixbufSetIconName :: a -> Maybe Text -> m ()
gutterRendererPixbufSetIconName renderer :: a
renderer iconName :: Maybe Text
iconName = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr GutterRendererPixbuf
renderer' <- a -> IO (Ptr GutterRendererPixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
renderer
    CString
maybeIconName <- case Maybe Text
iconName of
        Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just jIconName :: Text
jIconName -> do
            CString
jIconName' <- Text -> IO CString
textToCString Text
jIconName
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jIconName'
    Ptr GutterRendererPixbuf -> CString -> IO ()
gtk_source_gutter_renderer_pixbuf_set_icon_name Ptr GutterRendererPixbuf
renderer' CString
maybeIconName
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
renderer
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeIconName
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data GutterRendererPixbufSetIconNameMethodInfo
instance (signature ~ (Maybe (T.Text) -> m ()), MonadIO m, IsGutterRendererPixbuf a) => O.MethodInfo GutterRendererPixbufSetIconNameMethodInfo a signature where
    overloadedMethod = gutterRendererPixbufSetIconName

#endif

-- method GutterRendererPixbuf::set_pixbuf
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "renderer"
--           , argType =
--               TInterface
--                 Name { namespace = "GtkSource" , name = "GutterRendererPixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkSourceGutterRendererPixbuf"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pixbuf"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the pixbuf, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_source_gutter_renderer_pixbuf_set_pixbuf" gtk_source_gutter_renderer_pixbuf_set_pixbuf :: 
    Ptr GutterRendererPixbuf ->             -- renderer : TInterface (Name {namespace = "GtkSource", name = "GutterRendererPixbuf"})
    Ptr GdkPixbuf.Pixbuf.Pixbuf ->          -- pixbuf : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    IO ()

-- | /No description available in the introspection data./
gutterRendererPixbufSetPixbuf ::
    (B.CallStack.HasCallStack, MonadIO m, IsGutterRendererPixbuf a, GdkPixbuf.Pixbuf.IsPixbuf b) =>
    a
    -- ^ /@renderer@/: a t'GI.GtkSource.Objects.GutterRendererPixbuf.GutterRendererPixbuf'
    -> Maybe (b)
    -- ^ /@pixbuf@/: the pixbuf, or 'P.Nothing'.
    -> m ()
gutterRendererPixbufSetPixbuf :: a -> Maybe b -> m ()
gutterRendererPixbufSetPixbuf renderer :: a
renderer pixbuf :: Maybe b
pixbuf = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr GutterRendererPixbuf
renderer' <- a -> IO (Ptr GutterRendererPixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
renderer
    Ptr Pixbuf
maybePixbuf <- case Maybe b
pixbuf of
        Nothing -> Ptr Pixbuf -> IO (Ptr Pixbuf)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Pixbuf
forall a. Ptr a
nullPtr
        Just jPixbuf :: b
jPixbuf -> do
            Ptr Pixbuf
jPixbuf' <- b -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jPixbuf
            Ptr Pixbuf -> IO (Ptr Pixbuf)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Pixbuf
jPixbuf'
    Ptr GutterRendererPixbuf -> Ptr Pixbuf -> IO ()
gtk_source_gutter_renderer_pixbuf_set_pixbuf Ptr GutterRendererPixbuf
renderer' Ptr Pixbuf
maybePixbuf
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
renderer
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
pixbuf b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data GutterRendererPixbufSetPixbufMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsGutterRendererPixbuf a, GdkPixbuf.Pixbuf.IsPixbuf b) => O.MethodInfo GutterRendererPixbufSetPixbufMethodInfo a signature where
    overloadedMethod = gutterRendererPixbufSetPixbuf

#endif

-- method GutterRendererPixbuf::set_stock_id
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "renderer"
--           , argType =
--               TInterface
--                 Name { namespace = "GtkSource" , name = "GutterRendererPixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkSourceGutterRendererPixbuf"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "stock_id"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the stock id" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_source_gutter_renderer_pixbuf_set_stock_id" gtk_source_gutter_renderer_pixbuf_set_stock_id :: 
    Ptr GutterRendererPixbuf ->             -- renderer : TInterface (Name {namespace = "GtkSource", name = "GutterRendererPixbuf"})
    CString ->                              -- stock_id : TBasicType TUTF8
    IO ()

{-# DEPRECATED gutterRendererPixbufSetStockId ["(Since version 3.10)","Don\\'t use this function."] #-}
-- | /No description available in the introspection data./
gutterRendererPixbufSetStockId ::
    (B.CallStack.HasCallStack, MonadIO m, IsGutterRendererPixbuf a) =>
    a
    -- ^ /@renderer@/: a t'GI.GtkSource.Objects.GutterRendererPixbuf.GutterRendererPixbuf'
    -> Maybe (T.Text)
    -- ^ /@stockId@/: the stock id
    -> m ()
gutterRendererPixbufSetStockId :: a -> Maybe Text -> m ()
gutterRendererPixbufSetStockId renderer :: a
renderer stockId :: Maybe Text
stockId = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr GutterRendererPixbuf
renderer' <- a -> IO (Ptr GutterRendererPixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
renderer
    CString
maybeStockId <- case Maybe Text
stockId of
        Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just jStockId :: Text
jStockId -> do
            CString
jStockId' <- Text -> IO CString
textToCString Text
jStockId
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jStockId'
    Ptr GutterRendererPixbuf -> CString -> IO ()
gtk_source_gutter_renderer_pixbuf_set_stock_id Ptr GutterRendererPixbuf
renderer' CString
maybeStockId
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
renderer
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeStockId
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data GutterRendererPixbufSetStockIdMethodInfo
instance (signature ~ (Maybe (T.Text) -> m ()), MonadIO m, IsGutterRendererPixbuf a) => O.MethodInfo GutterRendererPixbufSetStockIdMethodInfo a signature where
    overloadedMethod = gutterRendererPixbufSetStockId

#endif