{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The t'GI.Gtk.Objects.Image.Image' widget displays an image. Various kinds of object
-- can be displayed as an image; most typically, you would load a
-- t'GI.GdkPixbuf.Objects.Pixbuf.Pixbuf' (\"pixel buffer\") from a file, and then display that.
-- There’s a convenience function to do this, 'GI.Gtk.Objects.Image.imageNewFromFile',
-- used as follows:
-- 
-- === /C code/
-- >
-- >  GtkWidget *image;
-- >  image = gtk_image_new_from_file ("myfile.png");
-- 
-- If the file isn’t loaded successfully, the image will contain a
-- “broken image” icon similar to that used in many web browsers.
-- If you want to handle errors in loading the file yourself,
-- for example by displaying an error message, then load the image with
-- 'GI.GdkPixbuf.Objects.Pixbuf.pixbufNewFromFile', then create the t'GI.Gtk.Objects.Image.Image' with
-- 'GI.Gtk.Objects.Image.imageNewFromPixbuf'.
-- 
-- The image file may contain an animation, if so the t'GI.Gtk.Objects.Image.Image' will
-- display an animation (t'GI.GdkPixbuf.Objects.PixbufAnimation.PixbufAnimation') instead of a static image.
-- 
-- t'GI.Gtk.Objects.Image.Image' is a subclass of t'GI.Gtk.Objects.Misc.Misc', which implies that you can
-- align it (center, left, right) and add padding to it, using
-- t'GI.Gtk.Objects.Misc.Misc' methods.
-- 
-- t'GI.Gtk.Objects.Image.Image' is a “no window” widget (has no t'GI.Gdk.Objects.Window.Window' of its own),
-- so by default does not receive events. If you want to receive events
-- on the image, such as button clicks, place the image inside a
-- t'GI.Gtk.Objects.EventBox.EventBox', then connect to the event signals on the event box.
-- 
-- ## Handling button press events on a t'GI.Gtk.Objects.Image.Image'.
-- 
-- 
-- === /C code/
-- >
-- >  static gboolean
-- >  button_press_callback (GtkWidget      *event_box,
-- >                         GdkEventButton *event,
-- >                         gpointer        data)
-- >  {
-- >    g_print ("Event box clicked at coordinates %f,%f\n",
-- >             event->x, event->y);
-- >
-- >    // Returning TRUE means we handled the event, so the signal
-- >    // emission should be stopped (don’t call any further callbacks
-- >    // that may be connected). Return FALSE to continue invoking callbacks.
-- >    return TRUE;
-- >  }
-- >
-- >  static GtkWidget*
-- >  create_image (void)
-- >  {
-- >    GtkWidget *image;
-- >    GtkWidget *event_box;
-- >
-- >    image = gtk_image_new_from_file ("myfile.png");
-- >
-- >    event_box = gtk_event_box_new ();
-- >
-- >    gtk_container_add (GTK_CONTAINER (event_box), image);
-- >
-- >    g_signal_connect (G_OBJECT (event_box),
-- >                      "button_press_event",
-- >                      G_CALLBACK (button_press_callback),
-- >                      image);
-- >
-- >    return image;
-- >  }
-- 
-- 
-- When handling events on the event box, keep in mind that coordinates
-- in the image may be different from event box coordinates due to
-- the alignment and padding settings on the image (see t'GI.Gtk.Objects.Misc.Misc').
-- The simplest way to solve this is to set the alignment to 0.0
-- (left\/top), and set the padding to zero. Then the origin of
-- the image will be the same as the origin of the event box.
-- 
-- Sometimes an application will want to avoid depending on external data
-- files, such as image files. GTK+ comes with a program to avoid this,
-- called “gdk-pixbuf-csource”. This library
-- allows you to convert an image into a C variable declaration, which
-- can then be loaded into a t'GI.GdkPixbuf.Objects.Pixbuf.Pixbuf' using
-- 'GI.GdkPixbuf.Objects.Pixbuf.pixbufNewFromInline'.
-- 
-- = CSS nodes
-- 
-- GtkImage has a single CSS node with the name image. The style classes
-- may appear on image CSS nodes: .icon-dropshadow, .lowres-icon.

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

module GI.Gtk.Objects.Image
    ( 

-- * Exported types
    Image(..)                               ,
    IsImage                                 ,
    toImage                                 ,
    noImage                                 ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveImageMethod                      ,
#endif


-- ** clear #method:clear#

#if defined(ENABLE_OVERLOADING)
    ImageClearMethodInfo                    ,
#endif
    imageClear                              ,


-- ** getAnimation #method:getAnimation#

#if defined(ENABLE_OVERLOADING)
    ImageGetAnimationMethodInfo             ,
#endif
    imageGetAnimation                       ,


-- ** getGicon #method:getGicon#

#if defined(ENABLE_OVERLOADING)
    ImageGetGiconMethodInfo                 ,
#endif
    imageGetGicon                           ,


-- ** getIconName #method:getIconName#

#if defined(ENABLE_OVERLOADING)
    ImageGetIconNameMethodInfo              ,
#endif
    imageGetIconName                        ,


-- ** getIconSet #method:getIconSet#

#if defined(ENABLE_OVERLOADING)
    ImageGetIconSetMethodInfo               ,
#endif
    imageGetIconSet                         ,


-- ** getPixbuf #method:getPixbuf#

#if defined(ENABLE_OVERLOADING)
    ImageGetPixbufMethodInfo                ,
#endif
    imageGetPixbuf                          ,


-- ** getPixelSize #method:getPixelSize#

#if defined(ENABLE_OVERLOADING)
    ImageGetPixelSizeMethodInfo             ,
#endif
    imageGetPixelSize                       ,


-- ** getStock #method:getStock#

#if defined(ENABLE_OVERLOADING)
    ImageGetStockMethodInfo                 ,
#endif
    imageGetStock                           ,


-- ** getStorageType #method:getStorageType#

#if defined(ENABLE_OVERLOADING)
    ImageGetStorageTypeMethodInfo           ,
#endif
    imageGetStorageType                     ,


-- ** new #method:new#

    imageNew                                ,


-- ** newFromAnimation #method:newFromAnimation#

    imageNewFromAnimation                   ,


-- ** newFromFile #method:newFromFile#

    imageNewFromFile                        ,


-- ** newFromGicon #method:newFromGicon#

    imageNewFromGicon                       ,


-- ** newFromIconName #method:newFromIconName#

    imageNewFromIconName                    ,


-- ** newFromIconSet #method:newFromIconSet#

    imageNewFromIconSet                     ,


-- ** newFromPixbuf #method:newFromPixbuf#

    imageNewFromPixbuf                      ,


-- ** newFromResource #method:newFromResource#

    imageNewFromResource                    ,


-- ** newFromStock #method:newFromStock#

    imageNewFromStock                       ,


-- ** newFromSurface #method:newFromSurface#

    imageNewFromSurface                     ,


-- ** setFromAnimation #method:setFromAnimation#

#if defined(ENABLE_OVERLOADING)
    ImageSetFromAnimationMethodInfo         ,
#endif
    imageSetFromAnimation                   ,


-- ** setFromFile #method:setFromFile#

#if defined(ENABLE_OVERLOADING)
    ImageSetFromFileMethodInfo              ,
#endif
    imageSetFromFile                        ,


-- ** setFromGicon #method:setFromGicon#

#if defined(ENABLE_OVERLOADING)
    ImageSetFromGiconMethodInfo             ,
#endif
    imageSetFromGicon                       ,


-- ** setFromIconName #method:setFromIconName#

#if defined(ENABLE_OVERLOADING)
    ImageSetFromIconNameMethodInfo          ,
#endif
    imageSetFromIconName                    ,


-- ** setFromIconSet #method:setFromIconSet#

#if defined(ENABLE_OVERLOADING)
    ImageSetFromIconSetMethodInfo           ,
#endif
    imageSetFromIconSet                     ,


-- ** setFromPixbuf #method:setFromPixbuf#

#if defined(ENABLE_OVERLOADING)
    ImageSetFromPixbufMethodInfo            ,
#endif
    imageSetFromPixbuf                      ,


-- ** setFromResource #method:setFromResource#

#if defined(ENABLE_OVERLOADING)
    ImageSetFromResourceMethodInfo          ,
#endif
    imageSetFromResource                    ,


-- ** setFromStock #method:setFromStock#

#if defined(ENABLE_OVERLOADING)
    ImageSetFromStockMethodInfo             ,
#endif
    imageSetFromStock                       ,


-- ** setFromSurface #method:setFromSurface#

#if defined(ENABLE_OVERLOADING)
    ImageSetFromSurfaceMethodInfo           ,
#endif
    imageSetFromSurface                     ,


-- ** setPixelSize #method:setPixelSize#

#if defined(ENABLE_OVERLOADING)
    ImageSetPixelSizeMethodInfo             ,
#endif
    imageSetPixelSize                       ,




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

#if defined(ENABLE_OVERLOADING)
    ImageFilePropertyInfo                   ,
#endif
    clearImageFile                          ,
    constructImageFile                      ,
    getImageFile                            ,
#if defined(ENABLE_OVERLOADING)
    imageFile                               ,
#endif
    setImageFile                            ,


-- ** gicon #attr:gicon#
-- | The GIcon displayed in the GtkImage. For themed icons,
-- If the icon theme is changed, the image will be updated
-- automatically.
-- 
-- /Since: 2.14/

#if defined(ENABLE_OVERLOADING)
    ImageGiconPropertyInfo                  ,
#endif
    clearImageGicon                         ,
    constructImageGicon                     ,
    getImageGicon                           ,
#if defined(ENABLE_OVERLOADING)
    imageGicon                              ,
#endif
    setImageGicon                           ,


-- ** iconName #attr:iconName#
-- | The name of the icon in the icon theme. If the icon theme is
-- changed, the image will be updated automatically.
-- 
-- /Since: 2.6/

#if defined(ENABLE_OVERLOADING)
    ImageIconNamePropertyInfo               ,
#endif
    clearImageIconName                      ,
    constructImageIconName                  ,
    getImageIconName                        ,
#if defined(ENABLE_OVERLOADING)
    imageIconName                           ,
#endif
    setImageIconName                        ,


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

#if defined(ENABLE_OVERLOADING)
    ImageIconSetPropertyInfo                ,
#endif
    clearImageIconSet                       ,
    constructImageIconSet                   ,
    getImageIconSet                         ,
#if defined(ENABLE_OVERLOADING)
    imageIconSet                            ,
#endif
    setImageIconSet                         ,


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

#if defined(ENABLE_OVERLOADING)
    ImageIconSizePropertyInfo               ,
#endif
    constructImageIconSize                  ,
    getImageIconSize                        ,
#if defined(ENABLE_OVERLOADING)
    imageIconSize                           ,
#endif
    setImageIconSize                        ,


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

#if defined(ENABLE_OVERLOADING)
    ImagePixbufPropertyInfo                 ,
#endif
    clearImagePixbuf                        ,
    constructImagePixbuf                    ,
    getImagePixbuf                          ,
#if defined(ENABLE_OVERLOADING)
    imagePixbuf                             ,
#endif
    setImagePixbuf                          ,


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

#if defined(ENABLE_OVERLOADING)
    ImagePixbufAnimationPropertyInfo        ,
#endif
    clearImagePixbufAnimation               ,
    constructImagePixbufAnimation           ,
    getImagePixbufAnimation                 ,
#if defined(ENABLE_OVERLOADING)
    imagePixbufAnimation                    ,
#endif
    setImagePixbufAnimation                 ,


-- ** pixelSize #attr:pixelSize#
-- | The \"pixel-size\" property can be used to specify a fixed size
-- overriding the t'GI.Gtk.Objects.Image.Image':@/icon-size/@ property for images of type
-- 'GI.Gtk.Enums.ImageTypeIconName'.
-- 
-- /Since: 2.6/

#if defined(ENABLE_OVERLOADING)
    ImagePixelSizePropertyInfo              ,
#endif
    constructImagePixelSize                 ,
    getImagePixelSize                       ,
#if defined(ENABLE_OVERLOADING)
    imagePixelSize                          ,
#endif
    setImagePixelSize                       ,


-- ** resource #attr:resource#
-- | A path to a resource file to display.
-- 
-- /Since: 3.8/

#if defined(ENABLE_OVERLOADING)
    ImageResourcePropertyInfo               ,
#endif
    clearImageResource                      ,
    constructImageResource                  ,
    getImageResource                        ,
#if defined(ENABLE_OVERLOADING)
    imageResource                           ,
#endif
    setImageResource                        ,


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

#if defined(ENABLE_OVERLOADING)
    ImageStockPropertyInfo                  ,
#endif
    clearImageStock                         ,
    constructImageStock                     ,
    getImageStock                           ,
#if defined(ENABLE_OVERLOADING)
    imageStock                              ,
#endif
    setImageStock                           ,


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

#if defined(ENABLE_OVERLOADING)
    ImageStorageTypePropertyInfo            ,
#endif
    getImageStorageType                     ,
#if defined(ENABLE_OVERLOADING)
    imageStorageType                        ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    ImageSurfacePropertyInfo                ,
#endif
    clearImageSurface                       ,
    constructImageSurface                   ,
    getImageSurface                         ,
#if defined(ENABLE_OVERLOADING)
    imageSurface                            ,
#endif
    setImageSurface                         ,


-- ** useFallback #attr:useFallback#
-- | Whether the icon displayed in the GtkImage will use
-- standard icon names fallback. The value of this property
-- is only relevant for images of type 'GI.Gtk.Enums.ImageTypeIconName'
-- and 'GI.Gtk.Enums.ImageTypeGicon'.
-- 
-- /Since: 3.0/

#if defined(ENABLE_OVERLOADING)
    ImageUseFallbackPropertyInfo            ,
#endif
    constructImageUseFallback               ,
    getImageUseFallback                     ,
#if defined(ENABLE_OVERLOADING)
    imageUseFallback                        ,
#endif
    setImageUseFallback                     ,




    ) 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.Atk.Interfaces.ImplementorIface as Atk.ImplementorIface
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.GdkPixbuf.Objects.PixbufAnimation as GdkPixbuf.PixbufAnimation
import qualified GI.Gio.Interfaces.Icon as Gio.Icon
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Objects.Misc as Gtk.Misc
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget
import {-# SOURCE #-} qualified GI.Gtk.Structs.IconSet as Gtk.IconSet

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

instance GObject Image where
    gobjectType :: IO GType
gobjectType = IO GType
c_gtk_image_get_type
    

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

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

instance O.HasParentTypes Image
type instance O.ParentTypes Image = '[Gtk.Misc.Misc, Gtk.Widget.Widget, GObject.Object.Object, Atk.ImplementorIface.ImplementorIface, Gtk.Buildable.Buildable]

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

-- | A convenience alias for `Nothing` :: `Maybe` `Image`.
noImage :: Maybe Image
noImage :: Maybe Image
noImage = Maybe Image
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveImageMethod (t :: Symbol) (o :: *) :: * where
    ResolveImageMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
    ResolveImageMethod "addAccelerator" o = Gtk.Widget.WidgetAddAcceleratorMethodInfo
    ResolveImageMethod "addChild" o = Gtk.Buildable.BuildableAddChildMethodInfo
    ResolveImageMethod "addDeviceEvents" o = Gtk.Widget.WidgetAddDeviceEventsMethodInfo
    ResolveImageMethod "addEvents" o = Gtk.Widget.WidgetAddEventsMethodInfo
    ResolveImageMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
    ResolveImageMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
    ResolveImageMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveImageMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveImageMethod "canActivateAccel" o = Gtk.Widget.WidgetCanActivateAccelMethodInfo
    ResolveImageMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
    ResolveImageMethod "childNotify" o = Gtk.Widget.WidgetChildNotifyMethodInfo
    ResolveImageMethod "classPath" o = Gtk.Widget.WidgetClassPathMethodInfo
    ResolveImageMethod "clear" o = ImageClearMethodInfo
    ResolveImageMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
    ResolveImageMethod "constructChild" o = Gtk.Buildable.BuildableConstructChildMethodInfo
    ResolveImageMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
    ResolveImageMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
    ResolveImageMethod "customFinished" o = Gtk.Buildable.BuildableCustomFinishedMethodInfo
    ResolveImageMethod "customTagEnd" o = Gtk.Buildable.BuildableCustomTagEndMethodInfo
    ResolveImageMethod "customTagStart" o = Gtk.Buildable.BuildableCustomTagStartMethodInfo
    ResolveImageMethod "destroy" o = Gtk.Widget.WidgetDestroyMethodInfo
    ResolveImageMethod "destroyed" o = Gtk.Widget.WidgetDestroyedMethodInfo
    ResolveImageMethod "deviceIsShadowed" o = Gtk.Widget.WidgetDeviceIsShadowedMethodInfo
    ResolveImageMethod "dragBegin" o = Gtk.Widget.WidgetDragBeginMethodInfo
    ResolveImageMethod "dragBeginWithCoordinates" o = Gtk.Widget.WidgetDragBeginWithCoordinatesMethodInfo
    ResolveImageMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
    ResolveImageMethod "dragDestAddImageTargets" o = Gtk.Widget.WidgetDragDestAddImageTargetsMethodInfo
    ResolveImageMethod "dragDestAddTextTargets" o = Gtk.Widget.WidgetDragDestAddTextTargetsMethodInfo
    ResolveImageMethod "dragDestAddUriTargets" o = Gtk.Widget.WidgetDragDestAddUriTargetsMethodInfo
    ResolveImageMethod "dragDestFindTarget" o = Gtk.Widget.WidgetDragDestFindTargetMethodInfo
    ResolveImageMethod "dragDestGetTargetList" o = Gtk.Widget.WidgetDragDestGetTargetListMethodInfo
    ResolveImageMethod "dragDestGetTrackMotion" o = Gtk.Widget.WidgetDragDestGetTrackMotionMethodInfo
    ResolveImageMethod "dragDestSet" o = Gtk.Widget.WidgetDragDestSetMethodInfo
    ResolveImageMethod "dragDestSetProxy" o = Gtk.Widget.WidgetDragDestSetProxyMethodInfo
    ResolveImageMethod "dragDestSetTargetList" o = Gtk.Widget.WidgetDragDestSetTargetListMethodInfo
    ResolveImageMethod "dragDestSetTrackMotion" o = Gtk.Widget.WidgetDragDestSetTrackMotionMethodInfo
    ResolveImageMethod "dragDestUnset" o = Gtk.Widget.WidgetDragDestUnsetMethodInfo
    ResolveImageMethod "dragGetData" o = Gtk.Widget.WidgetDragGetDataMethodInfo
    ResolveImageMethod "dragHighlight" o = Gtk.Widget.WidgetDragHighlightMethodInfo
    ResolveImageMethod "dragSourceAddImageTargets" o = Gtk.Widget.WidgetDragSourceAddImageTargetsMethodInfo
    ResolveImageMethod "dragSourceAddTextTargets" o = Gtk.Widget.WidgetDragSourceAddTextTargetsMethodInfo
    ResolveImageMethod "dragSourceAddUriTargets" o = Gtk.Widget.WidgetDragSourceAddUriTargetsMethodInfo
    ResolveImageMethod "dragSourceGetTargetList" o = Gtk.Widget.WidgetDragSourceGetTargetListMethodInfo
    ResolveImageMethod "dragSourceSet" o = Gtk.Widget.WidgetDragSourceSetMethodInfo
    ResolveImageMethod "dragSourceSetIconGicon" o = Gtk.Widget.WidgetDragSourceSetIconGiconMethodInfo
    ResolveImageMethod "dragSourceSetIconName" o = Gtk.Widget.WidgetDragSourceSetIconNameMethodInfo
    ResolveImageMethod "dragSourceSetIconPixbuf" o = Gtk.Widget.WidgetDragSourceSetIconPixbufMethodInfo
    ResolveImageMethod "dragSourceSetIconStock" o = Gtk.Widget.WidgetDragSourceSetIconStockMethodInfo
    ResolveImageMethod "dragSourceSetTargetList" o = Gtk.Widget.WidgetDragSourceSetTargetListMethodInfo
    ResolveImageMethod "dragSourceUnset" o = Gtk.Widget.WidgetDragSourceUnsetMethodInfo
    ResolveImageMethod "dragUnhighlight" o = Gtk.Widget.WidgetDragUnhighlightMethodInfo
    ResolveImageMethod "draw" o = Gtk.Widget.WidgetDrawMethodInfo
    ResolveImageMethod "ensureStyle" o = Gtk.Widget.WidgetEnsureStyleMethodInfo
    ResolveImageMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
    ResolveImageMethod "event" o = Gtk.Widget.WidgetEventMethodInfo
    ResolveImageMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveImageMethod "freezeChildNotify" o = Gtk.Widget.WidgetFreezeChildNotifyMethodInfo
    ResolveImageMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveImageMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveImageMethod "grabAdd" o = Gtk.Widget.WidgetGrabAddMethodInfo
    ResolveImageMethod "grabDefault" o = Gtk.Widget.WidgetGrabDefaultMethodInfo
    ResolveImageMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
    ResolveImageMethod "grabRemove" o = Gtk.Widget.WidgetGrabRemoveMethodInfo
    ResolveImageMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
    ResolveImageMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
    ResolveImageMethod "hasGrab" o = Gtk.Widget.WidgetHasGrabMethodInfo
    ResolveImageMethod "hasRcStyle" o = Gtk.Widget.WidgetHasRcStyleMethodInfo
    ResolveImageMethod "hasScreen" o = Gtk.Widget.WidgetHasScreenMethodInfo
    ResolveImageMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
    ResolveImageMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
    ResolveImageMethod "hideOnDelete" o = Gtk.Widget.WidgetHideOnDeleteMethodInfo
    ResolveImageMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
    ResolveImageMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
    ResolveImageMethod "inputShapeCombineRegion" o = Gtk.Widget.WidgetInputShapeCombineRegionMethodInfo
    ResolveImageMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
    ResolveImageMethod "intersect" o = Gtk.Widget.WidgetIntersectMethodInfo
    ResolveImageMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
    ResolveImageMethod "isComposited" o = Gtk.Widget.WidgetIsCompositedMethodInfo
    ResolveImageMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
    ResolveImageMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveImageMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
    ResolveImageMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
    ResolveImageMethod "isToplevel" o = Gtk.Widget.WidgetIsToplevelMethodInfo
    ResolveImageMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
    ResolveImageMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
    ResolveImageMethod "listAccelClosures" o = Gtk.Widget.WidgetListAccelClosuresMethodInfo
    ResolveImageMethod "listActionPrefixes" o = Gtk.Widget.WidgetListActionPrefixesMethodInfo
    ResolveImageMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
    ResolveImageMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
    ResolveImageMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
    ResolveImageMethod "modifyBase" o = Gtk.Widget.WidgetModifyBaseMethodInfo
    ResolveImageMethod "modifyBg" o = Gtk.Widget.WidgetModifyBgMethodInfo
    ResolveImageMethod "modifyCursor" o = Gtk.Widget.WidgetModifyCursorMethodInfo
    ResolveImageMethod "modifyFg" o = Gtk.Widget.WidgetModifyFgMethodInfo
    ResolveImageMethod "modifyFont" o = Gtk.Widget.WidgetModifyFontMethodInfo
    ResolveImageMethod "modifyStyle" o = Gtk.Widget.WidgetModifyStyleMethodInfo
    ResolveImageMethod "modifyText" o = Gtk.Widget.WidgetModifyTextMethodInfo
    ResolveImageMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveImageMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveImageMethod "overrideBackgroundColor" o = Gtk.Widget.WidgetOverrideBackgroundColorMethodInfo
    ResolveImageMethod "overrideColor" o = Gtk.Widget.WidgetOverrideColorMethodInfo
    ResolveImageMethod "overrideCursor" o = Gtk.Widget.WidgetOverrideCursorMethodInfo
    ResolveImageMethod "overrideFont" o = Gtk.Widget.WidgetOverrideFontMethodInfo
    ResolveImageMethod "overrideSymbolicColor" o = Gtk.Widget.WidgetOverrideSymbolicColorMethodInfo
    ResolveImageMethod "parserFinished" o = Gtk.Buildable.BuildableParserFinishedMethodInfo
    ResolveImageMethod "path" o = Gtk.Widget.WidgetPathMethodInfo
    ResolveImageMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
    ResolveImageMethod "queueComputeExpand" o = Gtk.Widget.WidgetQueueComputeExpandMethodInfo
    ResolveImageMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
    ResolveImageMethod "queueDrawArea" o = Gtk.Widget.WidgetQueueDrawAreaMethodInfo
    ResolveImageMethod "queueDrawRegion" o = Gtk.Widget.WidgetQueueDrawRegionMethodInfo
    ResolveImageMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
    ResolveImageMethod "queueResizeNoRedraw" o = Gtk.Widget.WidgetQueueResizeNoRedrawMethodInfo
    ResolveImageMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
    ResolveImageMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveImageMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveImageMethod "regionIntersect" o = Gtk.Widget.WidgetRegionIntersectMethodInfo
    ResolveImageMethod "registerWindow" o = Gtk.Widget.WidgetRegisterWindowMethodInfo
    ResolveImageMethod "removeAccelerator" o = Gtk.Widget.WidgetRemoveAcceleratorMethodInfo
    ResolveImageMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
    ResolveImageMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
    ResolveImageMethod "renderIcon" o = Gtk.Widget.WidgetRenderIconMethodInfo
    ResolveImageMethod "renderIconPixbuf" o = Gtk.Widget.WidgetRenderIconPixbufMethodInfo
    ResolveImageMethod "reparent" o = Gtk.Widget.WidgetReparentMethodInfo
    ResolveImageMethod "resetRcStyles" o = Gtk.Widget.WidgetResetRcStylesMethodInfo
    ResolveImageMethod "resetStyle" o = Gtk.Widget.WidgetResetStyleMethodInfo
    ResolveImageMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveImageMethod "sendExpose" o = Gtk.Widget.WidgetSendExposeMethodInfo
    ResolveImageMethod "sendFocusChange" o = Gtk.Widget.WidgetSendFocusChangeMethodInfo
    ResolveImageMethod "shapeCombineRegion" o = Gtk.Widget.WidgetShapeCombineRegionMethodInfo
    ResolveImageMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
    ResolveImageMethod "showAll" o = Gtk.Widget.WidgetShowAllMethodInfo
    ResolveImageMethod "showNow" o = Gtk.Widget.WidgetShowNowMethodInfo
    ResolveImageMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
    ResolveImageMethod "sizeAllocateWithBaseline" o = Gtk.Widget.WidgetSizeAllocateWithBaselineMethodInfo
    ResolveImageMethod "sizeRequest" o = Gtk.Widget.WidgetSizeRequestMethodInfo
    ResolveImageMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveImageMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveImageMethod "styleAttach" o = Gtk.Widget.WidgetStyleAttachMethodInfo
    ResolveImageMethod "styleGetProperty" o = Gtk.Widget.WidgetStyleGetPropertyMethodInfo
    ResolveImageMethod "thawChildNotify" o = Gtk.Widget.WidgetThawChildNotifyMethodInfo
    ResolveImageMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveImageMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
    ResolveImageMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
    ResolveImageMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
    ResolveImageMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
    ResolveImageMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
    ResolveImageMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveImageMethod "unregisterWindow" o = Gtk.Widget.WidgetUnregisterWindowMethodInfo
    ResolveImageMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
    ResolveImageMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveImageMethod "getAccessible" o = Gtk.Widget.WidgetGetAccessibleMethodInfo
    ResolveImageMethod "getActionGroup" o = Gtk.Widget.WidgetGetActionGroupMethodInfo
    ResolveImageMethod "getAlignment" o = Gtk.Misc.MiscGetAlignmentMethodInfo
    ResolveImageMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
    ResolveImageMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
    ResolveImageMethod "getAllocatedSize" o = Gtk.Widget.WidgetGetAllocatedSizeMethodInfo
    ResolveImageMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
    ResolveImageMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
    ResolveImageMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
    ResolveImageMethod "getAnimation" o = ImageGetAnimationMethodInfo
    ResolveImageMethod "getAppPaintable" o = Gtk.Widget.WidgetGetAppPaintableMethodInfo
    ResolveImageMethod "getCanDefault" o = Gtk.Widget.WidgetGetCanDefaultMethodInfo
    ResolveImageMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
    ResolveImageMethod "getChildRequisition" o = Gtk.Widget.WidgetGetChildRequisitionMethodInfo
    ResolveImageMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
    ResolveImageMethod "getClip" o = Gtk.Widget.WidgetGetClipMethodInfo
    ResolveImageMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
    ResolveImageMethod "getCompositeName" o = Gtk.Widget.WidgetGetCompositeNameMethodInfo
    ResolveImageMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveImageMethod "getDeviceEnabled" o = Gtk.Widget.WidgetGetDeviceEnabledMethodInfo
    ResolveImageMethod "getDeviceEvents" o = Gtk.Widget.WidgetGetDeviceEventsMethodInfo
    ResolveImageMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
    ResolveImageMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
    ResolveImageMethod "getDoubleBuffered" o = Gtk.Widget.WidgetGetDoubleBufferedMethodInfo
    ResolveImageMethod "getEvents" o = Gtk.Widget.WidgetGetEventsMethodInfo
    ResolveImageMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
    ResolveImageMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
    ResolveImageMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
    ResolveImageMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
    ResolveImageMethod "getGicon" o = ImageGetGiconMethodInfo
    ResolveImageMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
    ResolveImageMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
    ResolveImageMethod "getHasWindow" o = Gtk.Widget.WidgetGetHasWindowMethodInfo
    ResolveImageMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
    ResolveImageMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
    ResolveImageMethod "getIconName" o = ImageGetIconNameMethodInfo
    ResolveImageMethod "getIconSet" o = ImageGetIconSetMethodInfo
    ResolveImageMethod "getInternalChild" o = Gtk.Buildable.BuildableGetInternalChildMethodInfo
    ResolveImageMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
    ResolveImageMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
    ResolveImageMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
    ResolveImageMethod "getMarginLeft" o = Gtk.Widget.WidgetGetMarginLeftMethodInfo
    ResolveImageMethod "getMarginRight" o = Gtk.Widget.WidgetGetMarginRightMethodInfo
    ResolveImageMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
    ResolveImageMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
    ResolveImageMethod "getModifierMask" o = Gtk.Widget.WidgetGetModifierMaskMethodInfo
    ResolveImageMethod "getModifierStyle" o = Gtk.Widget.WidgetGetModifierStyleMethodInfo
    ResolveImageMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
    ResolveImageMethod "getNoShowAll" o = Gtk.Widget.WidgetGetNoShowAllMethodInfo
    ResolveImageMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
    ResolveImageMethod "getPadding" o = Gtk.Misc.MiscGetPaddingMethodInfo
    ResolveImageMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
    ResolveImageMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
    ResolveImageMethod "getParentWindow" o = Gtk.Widget.WidgetGetParentWindowMethodInfo
    ResolveImageMethod "getPath" o = Gtk.Widget.WidgetGetPathMethodInfo
    ResolveImageMethod "getPixbuf" o = ImageGetPixbufMethodInfo
    ResolveImageMethod "getPixelSize" o = ImageGetPixelSizeMethodInfo
    ResolveImageMethod "getPointer" o = Gtk.Widget.WidgetGetPointerMethodInfo
    ResolveImageMethod "getPreferredHeight" o = Gtk.Widget.WidgetGetPreferredHeightMethodInfo
    ResolveImageMethod "getPreferredHeightAndBaselineForWidth" o = Gtk.Widget.WidgetGetPreferredHeightAndBaselineForWidthMethodInfo
    ResolveImageMethod "getPreferredHeightForWidth" o = Gtk.Widget.WidgetGetPreferredHeightForWidthMethodInfo
    ResolveImageMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
    ResolveImageMethod "getPreferredWidth" o = Gtk.Widget.WidgetGetPreferredWidthMethodInfo
    ResolveImageMethod "getPreferredWidthForHeight" o = Gtk.Widget.WidgetGetPreferredWidthForHeightMethodInfo
    ResolveImageMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveImageMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveImageMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
    ResolveImageMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
    ResolveImageMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
    ResolveImageMethod "getRequisition" o = Gtk.Widget.WidgetGetRequisitionMethodInfo
    ResolveImageMethod "getRootWindow" o = Gtk.Widget.WidgetGetRootWindowMethodInfo
    ResolveImageMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
    ResolveImageMethod "getScreen" o = Gtk.Widget.WidgetGetScreenMethodInfo
    ResolveImageMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
    ResolveImageMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
    ResolveImageMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
    ResolveImageMethod "getState" o = Gtk.Widget.WidgetGetStateMethodInfo
    ResolveImageMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
    ResolveImageMethod "getStock" o = ImageGetStockMethodInfo
    ResolveImageMethod "getStorageType" o = ImageGetStorageTypeMethodInfo
    ResolveImageMethod "getStyle" o = Gtk.Widget.WidgetGetStyleMethodInfo
    ResolveImageMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
    ResolveImageMethod "getSupportMultidevice" o = Gtk.Widget.WidgetGetSupportMultideviceMethodInfo
    ResolveImageMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
    ResolveImageMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
    ResolveImageMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
    ResolveImageMethod "getTooltipWindow" o = Gtk.Widget.WidgetGetTooltipWindowMethodInfo
    ResolveImageMethod "getToplevel" o = Gtk.Widget.WidgetGetToplevelMethodInfo
    ResolveImageMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
    ResolveImageMethod "getValignWithBaseline" o = Gtk.Widget.WidgetGetValignWithBaselineMethodInfo
    ResolveImageMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
    ResolveImageMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
    ResolveImageMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
    ResolveImageMethod "getVisual" o = Gtk.Widget.WidgetGetVisualMethodInfo
    ResolveImageMethod "getWindow" o = Gtk.Widget.WidgetGetWindowMethodInfo
    ResolveImageMethod "setAccelPath" o = Gtk.Widget.WidgetSetAccelPathMethodInfo
    ResolveImageMethod "setAlignment" o = Gtk.Misc.MiscSetAlignmentMethodInfo
    ResolveImageMethod "setAllocation" o = Gtk.Widget.WidgetSetAllocationMethodInfo
    ResolveImageMethod "setAppPaintable" o = Gtk.Widget.WidgetSetAppPaintableMethodInfo
    ResolveImageMethod "setBuildableProperty" o = Gtk.Buildable.BuildableSetBuildablePropertyMethodInfo
    ResolveImageMethod "setCanDefault" o = Gtk.Widget.WidgetSetCanDefaultMethodInfo
    ResolveImageMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
    ResolveImageMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
    ResolveImageMethod "setClip" o = Gtk.Widget.WidgetSetClipMethodInfo
    ResolveImageMethod "setCompositeName" o = Gtk.Widget.WidgetSetCompositeNameMethodInfo
    ResolveImageMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveImageMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveImageMethod "setDeviceEnabled" o = Gtk.Widget.WidgetSetDeviceEnabledMethodInfo
    ResolveImageMethod "setDeviceEvents" o = Gtk.Widget.WidgetSetDeviceEventsMethodInfo
    ResolveImageMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
    ResolveImageMethod "setDoubleBuffered" o = Gtk.Widget.WidgetSetDoubleBufferedMethodInfo
    ResolveImageMethod "setEvents" o = Gtk.Widget.WidgetSetEventsMethodInfo
    ResolveImageMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
    ResolveImageMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
    ResolveImageMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
    ResolveImageMethod "setFromAnimation" o = ImageSetFromAnimationMethodInfo
    ResolveImageMethod "setFromFile" o = ImageSetFromFileMethodInfo
    ResolveImageMethod "setFromGicon" o = ImageSetFromGiconMethodInfo
    ResolveImageMethod "setFromIconName" o = ImageSetFromIconNameMethodInfo
    ResolveImageMethod "setFromIconSet" o = ImageSetFromIconSetMethodInfo
    ResolveImageMethod "setFromPixbuf" o = ImageSetFromPixbufMethodInfo
    ResolveImageMethod "setFromResource" o = ImageSetFromResourceMethodInfo
    ResolveImageMethod "setFromStock" o = ImageSetFromStockMethodInfo
    ResolveImageMethod "setFromSurface" o = ImageSetFromSurfaceMethodInfo
    ResolveImageMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
    ResolveImageMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
    ResolveImageMethod "setHasWindow" o = Gtk.Widget.WidgetSetHasWindowMethodInfo
    ResolveImageMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
    ResolveImageMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
    ResolveImageMethod "setMapped" o = Gtk.Widget.WidgetSetMappedMethodInfo
    ResolveImageMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
    ResolveImageMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
    ResolveImageMethod "setMarginLeft" o = Gtk.Widget.WidgetSetMarginLeftMethodInfo
    ResolveImageMethod "setMarginRight" o = Gtk.Widget.WidgetSetMarginRightMethodInfo
    ResolveImageMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
    ResolveImageMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
    ResolveImageMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
    ResolveImageMethod "setNoShowAll" o = Gtk.Widget.WidgetSetNoShowAllMethodInfo
    ResolveImageMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
    ResolveImageMethod "setPadding" o = Gtk.Misc.MiscSetPaddingMethodInfo
    ResolveImageMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
    ResolveImageMethod "setParentWindow" o = Gtk.Widget.WidgetSetParentWindowMethodInfo
    ResolveImageMethod "setPixelSize" o = ImageSetPixelSizeMethodInfo
    ResolveImageMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveImageMethod "setRealized" o = Gtk.Widget.WidgetSetRealizedMethodInfo
    ResolveImageMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
    ResolveImageMethod "setRedrawOnAllocate" o = Gtk.Widget.WidgetSetRedrawOnAllocateMethodInfo
    ResolveImageMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
    ResolveImageMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
    ResolveImageMethod "setState" o = Gtk.Widget.WidgetSetStateMethodInfo
    ResolveImageMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
    ResolveImageMethod "setStyle" o = Gtk.Widget.WidgetSetStyleMethodInfo
    ResolveImageMethod "setSupportMultidevice" o = Gtk.Widget.WidgetSetSupportMultideviceMethodInfo
    ResolveImageMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
    ResolveImageMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
    ResolveImageMethod "setTooltipWindow" o = Gtk.Widget.WidgetSetTooltipWindowMethodInfo
    ResolveImageMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
    ResolveImageMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
    ResolveImageMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
    ResolveImageMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
    ResolveImageMethod "setVisual" o = Gtk.Widget.WidgetSetVisualMethodInfo
    ResolveImageMethod "setWindow" o = Gtk.Widget.WidgetSetWindowMethodInfo
    ResolveImageMethod l o = O.MethodResolutionFailed l o

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

#endif

-- VVV Prop "file"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@file@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' image #file
-- @
getImageFile :: (MonadIO m, IsImage o) => o -> m (Maybe T.Text)
getImageFile :: o -> m (Maybe Text)
getImageFile 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 "file"

-- | Set the value of the “@file@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' image [ #file 'Data.GI.Base.Attributes.:=' value ]
-- @
setImageFile :: (MonadIO m, IsImage o) => o -> T.Text -> m ()
setImageFile :: o -> Text -> m ()
setImageFile 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 "file" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@file@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructImageFile :: (IsImage o) => T.Text -> IO (GValueConstruct o)
constructImageFile :: Text -> IO (GValueConstruct o)
constructImageFile val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "file" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Set the value of the “@file@” 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' #file
-- @
clearImageFile :: (MonadIO m, IsImage o) => o -> m ()
clearImageFile :: o -> m ()
clearImageFile 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 "file" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data ImageFilePropertyInfo
instance AttrInfo ImageFilePropertyInfo where
    type AttrAllowedOps ImageFilePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ImageFilePropertyInfo = IsImage
    type AttrSetTypeConstraint ImageFilePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint ImageFilePropertyInfo = (~) T.Text
    type AttrTransferType ImageFilePropertyInfo = T.Text
    type AttrGetType ImageFilePropertyInfo = (Maybe T.Text)
    type AttrLabel ImageFilePropertyInfo = "file"
    type AttrOrigin ImageFilePropertyInfo = Image
    attrGet = getImageFile
    attrSet = setImageFile
    attrTransfer _ v = do
        return v
    attrConstruct = constructImageFile
    attrClear = clearImageFile
#endif

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

-- | 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' image #gicon
-- @
getImageGicon :: (MonadIO m, IsImage o) => o -> m (Maybe Gio.Icon.Icon)
getImageGicon :: o -> m (Maybe Icon)
getImageGicon 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

-- | 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' image [ #gicon 'Data.GI.Base.Attributes.:=' value ]
-- @
setImageGicon :: (MonadIO m, IsImage o, Gio.Icon.IsIcon a) => o -> a -> m ()
setImageGicon :: o -> a -> m ()
setImageGicon 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`.
constructImageGicon :: (IsImage o, Gio.Icon.IsIcon a) => a -> IO (GValueConstruct o)
constructImageGicon :: a -> IO (GValueConstruct o)
constructImageGicon 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
-- @
clearImageGicon :: (MonadIO m, IsImage o) => o -> m ()
clearImageGicon :: o -> m ()
clearImageGicon 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 ImageGiconPropertyInfo
instance AttrInfo ImageGiconPropertyInfo where
    type AttrAllowedOps ImageGiconPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ImageGiconPropertyInfo = IsImage
    type AttrSetTypeConstraint ImageGiconPropertyInfo = Gio.Icon.IsIcon
    type AttrTransferTypeConstraint ImageGiconPropertyInfo = Gio.Icon.IsIcon
    type AttrTransferType ImageGiconPropertyInfo = Gio.Icon.Icon
    type AttrGetType ImageGiconPropertyInfo = (Maybe Gio.Icon.Icon)
    type AttrLabel ImageGiconPropertyInfo = "gicon"
    type AttrOrigin ImageGiconPropertyInfo = Image
    attrGet = getImageGicon
    attrSet = setImageGicon
    attrTransfer _ v = do
        unsafeCastTo Gio.Icon.Icon v
    attrConstruct = constructImageGicon
    attrClear = clearImageGicon
#endif

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

-- | 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' image #iconName
-- @
getImageIconName :: (MonadIO m, IsImage o) => o -> m (Maybe T.Text)
getImageIconName :: o -> m (Maybe Text)
getImageIconName 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"

-- | 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' image [ #iconName 'Data.GI.Base.Attributes.:=' value ]
-- @
setImageIconName :: (MonadIO m, IsImage o) => o -> T.Text -> m ()
setImageIconName :: o -> Text -> m ()
setImageIconName 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`.
constructImageIconName :: (IsImage o) => T.Text -> IO (GValueConstruct o)
constructImageIconName :: Text -> IO (GValueConstruct o)
constructImageIconName 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
-- @
clearImageIconName :: (MonadIO m, IsImage o) => o -> m ()
clearImageIconName :: o -> m ()
clearImageIconName 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 ImageIconNamePropertyInfo
instance AttrInfo ImageIconNamePropertyInfo where
    type AttrAllowedOps ImageIconNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ImageIconNamePropertyInfo = IsImage
    type AttrSetTypeConstraint ImageIconNamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint ImageIconNamePropertyInfo = (~) T.Text
    type AttrTransferType ImageIconNamePropertyInfo = T.Text
    type AttrGetType ImageIconNamePropertyInfo = (Maybe T.Text)
    type AttrLabel ImageIconNamePropertyInfo = "icon-name"
    type AttrOrigin ImageIconNamePropertyInfo = Image
    attrGet = getImageIconName
    attrSet = setImageIconName
    attrTransfer _ v = do
        return v
    attrConstruct = constructImageIconName
    attrClear = clearImageIconName
#endif

-- VVV Prop "icon-set"
   -- Type: TInterface (Name {namespace = "Gtk", name = "IconSet"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@icon-set@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' image #iconSet
-- @
getImageIconSet :: (MonadIO m, IsImage o) => o -> m (Maybe Gtk.IconSet.IconSet)
getImageIconSet :: o -> m (Maybe IconSet)
getImageIconSet obj :: o
obj = IO (Maybe IconSet) -> m (Maybe IconSet)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe IconSet) -> m (Maybe IconSet))
-> IO (Maybe IconSet) -> m (Maybe IconSet)
forall a b. (a -> b) -> a -> b
$ o
-> String -> (ManagedPtr IconSet -> IconSet) -> IO (Maybe IconSet)
forall a b.
(GObject a, BoxedObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyBoxed o
obj "icon-set" ManagedPtr IconSet -> IconSet
Gtk.IconSet.IconSet

-- | Set the value of the “@icon-set@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' image [ #iconSet 'Data.GI.Base.Attributes.:=' value ]
-- @
setImageIconSet :: (MonadIO m, IsImage o) => o -> Gtk.IconSet.IconSet -> m ()
setImageIconSet :: o -> IconSet -> m ()
setImageIconSet obj :: o
obj val :: IconSet
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 IconSet -> IO ()
forall a b.
(GObject a, BoxedObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyBoxed o
obj "icon-set" (IconSet -> Maybe IconSet
forall a. a -> Maybe a
Just IconSet
val)

-- | Construct a `GValueConstruct` with valid value for the “@icon-set@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructImageIconSet :: (IsImage o) => Gtk.IconSet.IconSet -> IO (GValueConstruct o)
constructImageIconSet :: IconSet -> IO (GValueConstruct o)
constructImageIconSet val :: IconSet
val = String -> Maybe IconSet -> IO (GValueConstruct o)
forall a o.
BoxedObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBoxed "icon-set" (IconSet -> Maybe IconSet
forall a. a -> Maybe a
Just IconSet
val)

-- | Set the value of the “@icon-set@” 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' #iconSet
-- @
clearImageIconSet :: (MonadIO m, IsImage o) => o -> m ()
clearImageIconSet :: o -> m ()
clearImageIconSet 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 IconSet -> IO ()
forall a b.
(GObject a, BoxedObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyBoxed o
obj "icon-set" (Maybe IconSet
forall a. Maybe a
Nothing :: Maybe Gtk.IconSet.IconSet)

#if defined(ENABLE_OVERLOADING)
data ImageIconSetPropertyInfo
instance AttrInfo ImageIconSetPropertyInfo where
    type AttrAllowedOps ImageIconSetPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ImageIconSetPropertyInfo = IsImage
    type AttrSetTypeConstraint ImageIconSetPropertyInfo = (~) Gtk.IconSet.IconSet
    type AttrTransferTypeConstraint ImageIconSetPropertyInfo = (~) Gtk.IconSet.IconSet
    type AttrTransferType ImageIconSetPropertyInfo = Gtk.IconSet.IconSet
    type AttrGetType ImageIconSetPropertyInfo = (Maybe Gtk.IconSet.IconSet)
    type AttrLabel ImageIconSetPropertyInfo = "icon-set"
    type AttrOrigin ImageIconSetPropertyInfo = Image
    attrGet = getImageIconSet
    attrSet = setImageIconSet
    attrTransfer _ v = do
        return v
    attrConstruct = constructImageIconSet
    attrClear = clearImageIconSet
#endif

-- VVV Prop "icon-size"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@icon-size@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' image #iconSize
-- @
getImageIconSize :: (MonadIO m, IsImage o) => o -> m Int32
getImageIconSize :: o -> m Int32
getImageIconSize obj :: o
obj = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj "icon-size"

-- | Set the value of the “@icon-size@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' image [ #iconSize 'Data.GI.Base.Attributes.:=' value ]
-- @
setImageIconSize :: (MonadIO m, IsImage o) => o -> Int32 -> m ()
setImageIconSize :: o -> Int32 -> m ()
setImageIconSize obj :: o
obj val :: Int32
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 -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj "icon-size" Int32
val

-- | Construct a `GValueConstruct` with valid value for the “@icon-size@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructImageIconSize :: (IsImage o) => Int32 -> IO (GValueConstruct o)
constructImageIconSize :: Int32 -> IO (GValueConstruct o)
constructImageIconSize val :: Int32
val = String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 "icon-size" Int32
val

#if defined(ENABLE_OVERLOADING)
data ImageIconSizePropertyInfo
instance AttrInfo ImageIconSizePropertyInfo where
    type AttrAllowedOps ImageIconSizePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ImageIconSizePropertyInfo = IsImage
    type AttrSetTypeConstraint ImageIconSizePropertyInfo = (~) Int32
    type AttrTransferTypeConstraint ImageIconSizePropertyInfo = (~) Int32
    type AttrTransferType ImageIconSizePropertyInfo = Int32
    type AttrGetType ImageIconSizePropertyInfo = Int32
    type AttrLabel ImageIconSizePropertyInfo = "icon-size"
    type AttrOrigin ImageIconSizePropertyInfo = Image
    attrGet = getImageIconSize
    attrSet = setImageIconSize
    attrTransfer _ v = do
        return v
    attrConstruct = constructImageIconSize
    attrClear = undefined
#endif

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

-- | 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' image #pixbuf
-- @
getImagePixbuf :: (MonadIO m, IsImage o) => o -> m (Maybe GdkPixbuf.Pixbuf.Pixbuf)
getImagePixbuf :: o -> m (Maybe Pixbuf)
getImagePixbuf 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

-- | 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' image [ #pixbuf 'Data.GI.Base.Attributes.:=' value ]
-- @
setImagePixbuf :: (MonadIO m, IsImage o, GdkPixbuf.Pixbuf.IsPixbuf a) => o -> a -> m ()
setImagePixbuf :: o -> a -> m ()
setImagePixbuf 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`.
constructImagePixbuf :: (IsImage o, GdkPixbuf.Pixbuf.IsPixbuf a) => a -> IO (GValueConstruct o)
constructImagePixbuf :: a -> IO (GValueConstruct o)
constructImagePixbuf 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
-- @
clearImagePixbuf :: (MonadIO m, IsImage o) => o -> m ()
clearImagePixbuf :: o -> m ()
clearImagePixbuf 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 ImagePixbufPropertyInfo
instance AttrInfo ImagePixbufPropertyInfo where
    type AttrAllowedOps ImagePixbufPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ImagePixbufPropertyInfo = IsImage
    type AttrSetTypeConstraint ImagePixbufPropertyInfo = GdkPixbuf.Pixbuf.IsPixbuf
    type AttrTransferTypeConstraint ImagePixbufPropertyInfo = GdkPixbuf.Pixbuf.IsPixbuf
    type AttrTransferType ImagePixbufPropertyInfo = GdkPixbuf.Pixbuf.Pixbuf
    type AttrGetType ImagePixbufPropertyInfo = (Maybe GdkPixbuf.Pixbuf.Pixbuf)
    type AttrLabel ImagePixbufPropertyInfo = "pixbuf"
    type AttrOrigin ImagePixbufPropertyInfo = Image
    attrGet = getImagePixbuf
    attrSet = setImagePixbuf
    attrTransfer _ v = do
        unsafeCastTo GdkPixbuf.Pixbuf.Pixbuf v
    attrConstruct = constructImagePixbuf
    attrClear = clearImagePixbuf
#endif

-- VVV Prop "pixbuf-animation"
   -- Type: TInterface (Name {namespace = "GdkPixbuf", name = "PixbufAnimation"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@pixbuf-animation@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' image #pixbufAnimation
-- @
getImagePixbufAnimation :: (MonadIO m, IsImage o) => o -> m (Maybe GdkPixbuf.PixbufAnimation.PixbufAnimation)
getImagePixbufAnimation :: o -> m (Maybe PixbufAnimation)
getImagePixbufAnimation obj :: o
obj = IO (Maybe PixbufAnimation) -> m (Maybe PixbufAnimation)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe PixbufAnimation) -> m (Maybe PixbufAnimation))
-> IO (Maybe PixbufAnimation) -> m (Maybe PixbufAnimation)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr PixbufAnimation -> PixbufAnimation)
-> IO (Maybe PixbufAnimation)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj "pixbuf-animation" ManagedPtr PixbufAnimation -> PixbufAnimation
GdkPixbuf.PixbufAnimation.PixbufAnimation

-- | Set the value of the “@pixbuf-animation@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' image [ #pixbufAnimation 'Data.GI.Base.Attributes.:=' value ]
-- @
setImagePixbufAnimation :: (MonadIO m, IsImage o, GdkPixbuf.PixbufAnimation.IsPixbufAnimation a) => o -> a -> m ()
setImagePixbufAnimation :: o -> a -> m ()
setImagePixbufAnimation 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-animation" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Construct a `GValueConstruct` with valid value for the “@pixbuf-animation@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructImagePixbufAnimation :: (IsImage o, GdkPixbuf.PixbufAnimation.IsPixbufAnimation a) => a -> IO (GValueConstruct o)
constructImagePixbufAnimation :: a -> IO (GValueConstruct o)
constructImagePixbufAnimation val :: a
val = String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject "pixbuf-animation" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Set the value of the “@pixbuf-animation@” 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' #pixbufAnimation
-- @
clearImagePixbufAnimation :: (MonadIO m, IsImage o) => o -> m ()
clearImagePixbufAnimation :: o -> m ()
clearImagePixbufAnimation 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 PixbufAnimation -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj "pixbuf-animation" (Maybe PixbufAnimation
forall a. Maybe a
Nothing :: Maybe GdkPixbuf.PixbufAnimation.PixbufAnimation)

#if defined(ENABLE_OVERLOADING)
data ImagePixbufAnimationPropertyInfo
instance AttrInfo ImagePixbufAnimationPropertyInfo where
    type AttrAllowedOps ImagePixbufAnimationPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ImagePixbufAnimationPropertyInfo = IsImage
    type AttrSetTypeConstraint ImagePixbufAnimationPropertyInfo = GdkPixbuf.PixbufAnimation.IsPixbufAnimation
    type AttrTransferTypeConstraint ImagePixbufAnimationPropertyInfo = GdkPixbuf.PixbufAnimation.IsPixbufAnimation
    type AttrTransferType ImagePixbufAnimationPropertyInfo = GdkPixbuf.PixbufAnimation.PixbufAnimation
    type AttrGetType ImagePixbufAnimationPropertyInfo = (Maybe GdkPixbuf.PixbufAnimation.PixbufAnimation)
    type AttrLabel ImagePixbufAnimationPropertyInfo = "pixbuf-animation"
    type AttrOrigin ImagePixbufAnimationPropertyInfo = Image
    attrGet = getImagePixbufAnimation
    attrSet = setImagePixbufAnimation
    attrTransfer _ v = do
        unsafeCastTo GdkPixbuf.PixbufAnimation.PixbufAnimation v
    attrConstruct = constructImagePixbufAnimation
    attrClear = clearImagePixbufAnimation
#endif

-- VVV Prop "pixel-size"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@pixel-size@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' image #pixelSize
-- @
getImagePixelSize :: (MonadIO m, IsImage o) => o -> m Int32
getImagePixelSize :: o -> m Int32
getImagePixelSize obj :: o
obj = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj "pixel-size"

-- | Set the value of the “@pixel-size@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' image [ #pixelSize 'Data.GI.Base.Attributes.:=' value ]
-- @
setImagePixelSize :: (MonadIO m, IsImage o) => o -> Int32 -> m ()
setImagePixelSize :: o -> Int32 -> m ()
setImagePixelSize obj :: o
obj val :: Int32
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 -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj "pixel-size" Int32
val

-- | Construct a `GValueConstruct` with valid value for the “@pixel-size@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructImagePixelSize :: (IsImage o) => Int32 -> IO (GValueConstruct o)
constructImagePixelSize :: Int32 -> IO (GValueConstruct o)
constructImagePixelSize val :: Int32
val = String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 "pixel-size" Int32
val

#if defined(ENABLE_OVERLOADING)
data ImagePixelSizePropertyInfo
instance AttrInfo ImagePixelSizePropertyInfo where
    type AttrAllowedOps ImagePixelSizePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ImagePixelSizePropertyInfo = IsImage
    type AttrSetTypeConstraint ImagePixelSizePropertyInfo = (~) Int32
    type AttrTransferTypeConstraint ImagePixelSizePropertyInfo = (~) Int32
    type AttrTransferType ImagePixelSizePropertyInfo = Int32
    type AttrGetType ImagePixelSizePropertyInfo = Int32
    type AttrLabel ImagePixelSizePropertyInfo = "pixel-size"
    type AttrOrigin ImagePixelSizePropertyInfo = Image
    attrGet = getImagePixelSize
    attrSet = setImagePixelSize
    attrTransfer _ v = do
        return v
    attrConstruct = constructImagePixelSize
    attrClear = undefined
#endif

-- VVV Prop "resource"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@resource@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' image #resource
-- @
getImageResource :: (MonadIO m, IsImage o) => o -> m (Maybe T.Text)
getImageResource :: o -> m (Maybe Text)
getImageResource 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 "resource"

-- | Set the value of the “@resource@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' image [ #resource 'Data.GI.Base.Attributes.:=' value ]
-- @
setImageResource :: (MonadIO m, IsImage o) => o -> T.Text -> m ()
setImageResource :: o -> Text -> m ()
setImageResource 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 "resource" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@resource@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructImageResource :: (IsImage o) => T.Text -> IO (GValueConstruct o)
constructImageResource :: Text -> IO (GValueConstruct o)
constructImageResource val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "resource" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Set the value of the “@resource@” 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' #resource
-- @
clearImageResource :: (MonadIO m, IsImage o) => o -> m ()
clearImageResource :: o -> m ()
clearImageResource 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 "resource" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data ImageResourcePropertyInfo
instance AttrInfo ImageResourcePropertyInfo where
    type AttrAllowedOps ImageResourcePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ImageResourcePropertyInfo = IsImage
    type AttrSetTypeConstraint ImageResourcePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint ImageResourcePropertyInfo = (~) T.Text
    type AttrTransferType ImageResourcePropertyInfo = T.Text
    type AttrGetType ImageResourcePropertyInfo = (Maybe T.Text)
    type AttrLabel ImageResourcePropertyInfo = "resource"
    type AttrOrigin ImageResourcePropertyInfo = Image
    attrGet = getImageResource
    attrSet = setImageResource
    attrTransfer _ v = do
        return v
    attrConstruct = constructImageResource
    attrClear = clearImageResource
#endif

-- VVV Prop "stock"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@stock@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' image #stock
-- @
getImageStock :: (MonadIO m, IsImage o) => o -> m (Maybe T.Text)
getImageStock :: o -> m (Maybe Text)
getImageStock 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"

-- | Set the value of the “@stock@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' image [ #stock 'Data.GI.Base.Attributes.:=' value ]
-- @
setImageStock :: (MonadIO m, IsImage o) => o -> T.Text -> m ()
setImageStock :: o -> Text -> m ()
setImageStock 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" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@stock@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructImageStock :: (IsImage o) => T.Text -> IO (GValueConstruct o)
constructImageStock :: Text -> IO (GValueConstruct o)
constructImageStock val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "stock" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Set the value of the “@stock@” 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' #stock
-- @
clearImageStock :: (MonadIO m, IsImage o) => o -> m ()
clearImageStock :: o -> m ()
clearImageStock 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" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data ImageStockPropertyInfo
instance AttrInfo ImageStockPropertyInfo where
    type AttrAllowedOps ImageStockPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ImageStockPropertyInfo = IsImage
    type AttrSetTypeConstraint ImageStockPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint ImageStockPropertyInfo = (~) T.Text
    type AttrTransferType ImageStockPropertyInfo = T.Text
    type AttrGetType ImageStockPropertyInfo = (Maybe T.Text)
    type AttrLabel ImageStockPropertyInfo = "stock"
    type AttrOrigin ImageStockPropertyInfo = Image
    attrGet = getImageStock
    attrSet = setImageStock
    attrTransfer _ v = do
        return v
    attrConstruct = constructImageStock
    attrClear = clearImageStock
#endif

-- VVV Prop "storage-type"
   -- Type: TInterface (Name {namespace = "Gtk", name = "ImageType"})
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@storage-type@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' image #storageType
-- @
getImageStorageType :: (MonadIO m, IsImage o) => o -> m Gtk.Enums.ImageType
getImageStorageType :: o -> m ImageType
getImageStorageType obj :: o
obj = IO ImageType -> m ImageType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ImageType -> m ImageType) -> IO ImageType -> m ImageType
forall a b. (a -> b) -> a -> b
$ o -> String -> IO ImageType
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj "storage-type"

#if defined(ENABLE_OVERLOADING)
data ImageStorageTypePropertyInfo
instance AttrInfo ImageStorageTypePropertyInfo where
    type AttrAllowedOps ImageStorageTypePropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint ImageStorageTypePropertyInfo = IsImage
    type AttrSetTypeConstraint ImageStorageTypePropertyInfo = (~) ()
    type AttrTransferTypeConstraint ImageStorageTypePropertyInfo = (~) ()
    type AttrTransferType ImageStorageTypePropertyInfo = ()
    type AttrGetType ImageStorageTypePropertyInfo = Gtk.Enums.ImageType
    type AttrLabel ImageStorageTypePropertyInfo = "storage-type"
    type AttrOrigin ImageStorageTypePropertyInfo = Image
    attrGet = getImageStorageType
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

-- VVV Prop "surface"
   -- Type: TInterface (Name {namespace = "cairo", name = "Surface"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@surface@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' image #surface
-- @
getImageSurface :: (MonadIO m, IsImage o) => o -> m (Maybe Cairo.Surface.Surface)
getImageSurface :: o -> m (Maybe Surface)
getImageSurface 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

-- | Set the value of the “@surface@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' image [ #surface 'Data.GI.Base.Attributes.:=' value ]
-- @
setImageSurface :: (MonadIO m, IsImage o) => o -> Cairo.Surface.Surface -> m ()
setImageSurface :: o -> Surface -> m ()
setImageSurface 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)

-- | Construct a `GValueConstruct` with valid value for the “@surface@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructImageSurface :: (IsImage o) => Cairo.Surface.Surface -> IO (GValueConstruct o)
constructImageSurface :: Surface -> IO (GValueConstruct o)
constructImageSurface 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)

-- | Set the value of the “@surface@” 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' #surface
-- @
clearImageSurface :: (MonadIO m, IsImage o) => o -> m ()
clearImageSurface :: o -> m ()
clearImageSurface 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 ImageSurfacePropertyInfo
instance AttrInfo ImageSurfacePropertyInfo where
    type AttrAllowedOps ImageSurfacePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ImageSurfacePropertyInfo = IsImage
    type AttrSetTypeConstraint ImageSurfacePropertyInfo = (~) Cairo.Surface.Surface
    type AttrTransferTypeConstraint ImageSurfacePropertyInfo = (~) Cairo.Surface.Surface
    type AttrTransferType ImageSurfacePropertyInfo = Cairo.Surface.Surface
    type AttrGetType ImageSurfacePropertyInfo = (Maybe Cairo.Surface.Surface)
    type AttrLabel ImageSurfacePropertyInfo = "surface"
    type AttrOrigin ImageSurfacePropertyInfo = Image
    attrGet = getImageSurface
    attrSet = setImageSurface
    attrTransfer _ v = do
        return v
    attrConstruct = constructImageSurface
    attrClear = clearImageSurface
#endif

-- VVV Prop "use-fallback"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@use-fallback@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' image #useFallback
-- @
getImageUseFallback :: (MonadIO m, IsImage o) => o -> m Bool
getImageUseFallback :: o -> m Bool
getImageUseFallback 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 "use-fallback"

-- | Set the value of the “@use-fallback@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' image [ #useFallback 'Data.GI.Base.Attributes.:=' value ]
-- @
setImageUseFallback :: (MonadIO m, IsImage o) => o -> Bool -> m ()
setImageUseFallback :: o -> Bool -> m ()
setImageUseFallback 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 "use-fallback" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@use-fallback@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructImageUseFallback :: (IsImage o) => Bool -> IO (GValueConstruct o)
constructImageUseFallback :: Bool -> IO (GValueConstruct o)
constructImageUseFallback val :: Bool
val = String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool "use-fallback" Bool
val

#if defined(ENABLE_OVERLOADING)
data ImageUseFallbackPropertyInfo
instance AttrInfo ImageUseFallbackPropertyInfo where
    type AttrAllowedOps ImageUseFallbackPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ImageUseFallbackPropertyInfo = IsImage
    type AttrSetTypeConstraint ImageUseFallbackPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint ImageUseFallbackPropertyInfo = (~) Bool
    type AttrTransferType ImageUseFallbackPropertyInfo = Bool
    type AttrGetType ImageUseFallbackPropertyInfo = Bool
    type AttrLabel ImageUseFallbackPropertyInfo = "use-fallback"
    type AttrOrigin ImageUseFallbackPropertyInfo = Image
    attrGet = getImageUseFallback
    attrSet = setImageUseFallback
    attrTransfer _ v = do
        return v
    attrConstruct = constructImageUseFallback
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Image
type instance O.AttributeList Image = ImageAttributeList
type ImageAttributeList = ('[ '("appPaintable", Gtk.Widget.WidgetAppPaintablePropertyInfo), '("canDefault", Gtk.Widget.WidgetCanDefaultPropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("compositeChild", Gtk.Widget.WidgetCompositeChildPropertyInfo), '("doubleBuffered", Gtk.Widget.WidgetDoubleBufferedPropertyInfo), '("events", Gtk.Widget.WidgetEventsPropertyInfo), '("expand", Gtk.Widget.WidgetExpandPropertyInfo), '("file", ImageFilePropertyInfo), '("focusOnClick", Gtk.Widget.WidgetFocusOnClickPropertyInfo), '("gicon", ImageGiconPropertyInfo), '("halign", Gtk.Widget.WidgetHalignPropertyInfo), '("hasDefault", Gtk.Widget.WidgetHasDefaultPropertyInfo), '("hasFocus", Gtk.Widget.WidgetHasFocusPropertyInfo), '("hasTooltip", Gtk.Widget.WidgetHasTooltipPropertyInfo), '("heightRequest", Gtk.Widget.WidgetHeightRequestPropertyInfo), '("hexpand", Gtk.Widget.WidgetHexpandPropertyInfo), '("hexpandSet", Gtk.Widget.WidgetHexpandSetPropertyInfo), '("iconName", ImageIconNamePropertyInfo), '("iconSet", ImageIconSetPropertyInfo), '("iconSize", ImageIconSizePropertyInfo), '("isFocus", Gtk.Widget.WidgetIsFocusPropertyInfo), '("margin", Gtk.Widget.WidgetMarginPropertyInfo), '("marginBottom", Gtk.Widget.WidgetMarginBottomPropertyInfo), '("marginEnd", Gtk.Widget.WidgetMarginEndPropertyInfo), '("marginLeft", Gtk.Widget.WidgetMarginLeftPropertyInfo), '("marginRight", Gtk.Widget.WidgetMarginRightPropertyInfo), '("marginStart", Gtk.Widget.WidgetMarginStartPropertyInfo), '("marginTop", Gtk.Widget.WidgetMarginTopPropertyInfo), '("name", Gtk.Widget.WidgetNamePropertyInfo), '("noShowAll", Gtk.Widget.WidgetNoShowAllPropertyInfo), '("opacity", Gtk.Widget.WidgetOpacityPropertyInfo), '("parent", Gtk.Widget.WidgetParentPropertyInfo), '("pixbuf", ImagePixbufPropertyInfo), '("pixbufAnimation", ImagePixbufAnimationPropertyInfo), '("pixelSize", ImagePixelSizePropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("resource", ImageResourcePropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("stock", ImageStockPropertyInfo), '("storageType", ImageStorageTypePropertyInfo), '("style", Gtk.Widget.WidgetStylePropertyInfo), '("surface", ImageSurfacePropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("useFallback", ImageUseFallbackPropertyInfo), '("valign", Gtk.Widget.WidgetValignPropertyInfo), '("vexpand", Gtk.Widget.WidgetVexpandPropertyInfo), '("vexpandSet", Gtk.Widget.WidgetVexpandSetPropertyInfo), '("visible", Gtk.Widget.WidgetVisiblePropertyInfo), '("widthRequest", Gtk.Widget.WidgetWidthRequestPropertyInfo), '("window", Gtk.Widget.WidgetWindowPropertyInfo), '("xalign", Gtk.Misc.MiscXalignPropertyInfo), '("xpad", Gtk.Misc.MiscXpadPropertyInfo), '("yalign", Gtk.Misc.MiscYalignPropertyInfo), '("ypad", Gtk.Misc.MiscYpadPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
imageFile :: AttrLabelProxy "file"
imageFile = AttrLabelProxy

imageGicon :: AttrLabelProxy "gicon"
imageGicon = AttrLabelProxy

imageIconName :: AttrLabelProxy "iconName"
imageIconName = AttrLabelProxy

imageIconSet :: AttrLabelProxy "iconSet"
imageIconSet = AttrLabelProxy

imageIconSize :: AttrLabelProxy "iconSize"
imageIconSize = AttrLabelProxy

imagePixbuf :: AttrLabelProxy "pixbuf"
imagePixbuf = AttrLabelProxy

imagePixbufAnimation :: AttrLabelProxy "pixbufAnimation"
imagePixbufAnimation = AttrLabelProxy

imagePixelSize :: AttrLabelProxy "pixelSize"
imagePixelSize = AttrLabelProxy

imageResource :: AttrLabelProxy "resource"
imageResource = AttrLabelProxy

imageStock :: AttrLabelProxy "stock"
imageStock = AttrLabelProxy

imageStorageType :: AttrLabelProxy "storageType"
imageStorageType = AttrLabelProxy

imageSurface :: AttrLabelProxy "surface"
imageSurface = AttrLabelProxy

imageUseFallback :: AttrLabelProxy "useFallback"
imageUseFallback = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Image = ImageSignalList
type ImageSignalList = ('[ '("accelClosuresChanged", Gtk.Widget.WidgetAccelClosuresChangedSignalInfo), '("buttonPressEvent", Gtk.Widget.WidgetButtonPressEventSignalInfo), '("buttonReleaseEvent", Gtk.Widget.WidgetButtonReleaseEventSignalInfo), '("canActivateAccel", Gtk.Widget.WidgetCanActivateAccelSignalInfo), '("childNotify", Gtk.Widget.WidgetChildNotifySignalInfo), '("compositedChanged", Gtk.Widget.WidgetCompositedChangedSignalInfo), '("configureEvent", Gtk.Widget.WidgetConfigureEventSignalInfo), '("damageEvent", Gtk.Widget.WidgetDamageEventSignalInfo), '("deleteEvent", Gtk.Widget.WidgetDeleteEventSignalInfo), '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("destroyEvent", Gtk.Widget.WidgetDestroyEventSignalInfo), '("directionChanged", Gtk.Widget.WidgetDirectionChangedSignalInfo), '("dragBegin", Gtk.Widget.WidgetDragBeginSignalInfo), '("dragDataDelete", Gtk.Widget.WidgetDragDataDeleteSignalInfo), '("dragDataGet", Gtk.Widget.WidgetDragDataGetSignalInfo), '("dragDataReceived", Gtk.Widget.WidgetDragDataReceivedSignalInfo), '("dragDrop", Gtk.Widget.WidgetDragDropSignalInfo), '("dragEnd", Gtk.Widget.WidgetDragEndSignalInfo), '("dragFailed", Gtk.Widget.WidgetDragFailedSignalInfo), '("dragLeave", Gtk.Widget.WidgetDragLeaveSignalInfo), '("dragMotion", Gtk.Widget.WidgetDragMotionSignalInfo), '("draw", Gtk.Widget.WidgetDrawSignalInfo), '("enterNotifyEvent", Gtk.Widget.WidgetEnterNotifyEventSignalInfo), '("event", Gtk.Widget.WidgetEventSignalInfo), '("eventAfter", Gtk.Widget.WidgetEventAfterSignalInfo), '("focus", Gtk.Widget.WidgetFocusSignalInfo), '("focusInEvent", Gtk.Widget.WidgetFocusInEventSignalInfo), '("focusOutEvent", Gtk.Widget.WidgetFocusOutEventSignalInfo), '("grabBrokenEvent", Gtk.Widget.WidgetGrabBrokenEventSignalInfo), '("grabFocus", Gtk.Widget.WidgetGrabFocusSignalInfo), '("grabNotify", Gtk.Widget.WidgetGrabNotifySignalInfo), '("hide", Gtk.Widget.WidgetHideSignalInfo), '("hierarchyChanged", Gtk.Widget.WidgetHierarchyChangedSignalInfo), '("keyPressEvent", Gtk.Widget.WidgetKeyPressEventSignalInfo), '("keyReleaseEvent", Gtk.Widget.WidgetKeyReleaseEventSignalInfo), '("keynavFailed", Gtk.Widget.WidgetKeynavFailedSignalInfo), '("leaveNotifyEvent", Gtk.Widget.WidgetLeaveNotifyEventSignalInfo), '("map", Gtk.Widget.WidgetMapSignalInfo), '("mapEvent", Gtk.Widget.WidgetMapEventSignalInfo), '("mnemonicActivate", Gtk.Widget.WidgetMnemonicActivateSignalInfo), '("motionNotifyEvent", Gtk.Widget.WidgetMotionNotifyEventSignalInfo), '("moveFocus", Gtk.Widget.WidgetMoveFocusSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("parentSet", Gtk.Widget.WidgetParentSetSignalInfo), '("popupMenu", Gtk.Widget.WidgetPopupMenuSignalInfo), '("propertyNotifyEvent", Gtk.Widget.WidgetPropertyNotifyEventSignalInfo), '("proximityInEvent", Gtk.Widget.WidgetProximityInEventSignalInfo), '("proximityOutEvent", Gtk.Widget.WidgetProximityOutEventSignalInfo), '("queryTooltip", Gtk.Widget.WidgetQueryTooltipSignalInfo), '("realize", Gtk.Widget.WidgetRealizeSignalInfo), '("screenChanged", Gtk.Widget.WidgetScreenChangedSignalInfo), '("scrollEvent", Gtk.Widget.WidgetScrollEventSignalInfo), '("selectionClearEvent", Gtk.Widget.WidgetSelectionClearEventSignalInfo), '("selectionGet", Gtk.Widget.WidgetSelectionGetSignalInfo), '("selectionNotifyEvent", Gtk.Widget.WidgetSelectionNotifyEventSignalInfo), '("selectionReceived", Gtk.Widget.WidgetSelectionReceivedSignalInfo), '("selectionRequestEvent", Gtk.Widget.WidgetSelectionRequestEventSignalInfo), '("show", Gtk.Widget.WidgetShowSignalInfo), '("showHelp", Gtk.Widget.WidgetShowHelpSignalInfo), '("sizeAllocate", Gtk.Widget.WidgetSizeAllocateSignalInfo), '("stateChanged", Gtk.Widget.WidgetStateChangedSignalInfo), '("stateFlagsChanged", Gtk.Widget.WidgetStateFlagsChangedSignalInfo), '("styleSet", Gtk.Widget.WidgetStyleSetSignalInfo), '("styleUpdated", Gtk.Widget.WidgetStyleUpdatedSignalInfo), '("touchEvent", Gtk.Widget.WidgetTouchEventSignalInfo), '("unmap", Gtk.Widget.WidgetUnmapSignalInfo), '("unmapEvent", Gtk.Widget.WidgetUnmapEventSignalInfo), '("unrealize", Gtk.Widget.WidgetUnrealizeSignalInfo), '("visibilityNotifyEvent", Gtk.Widget.WidgetVisibilityNotifyEventSignalInfo), '("windowStateEvent", Gtk.Widget.WidgetWindowStateEventSignalInfo)] :: [(Symbol, *)])

#endif

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

foreign import ccall "gtk_image_new" gtk_image_new :: 
    IO (Ptr Image)

-- | Creates a new empty t'GI.Gtk.Objects.Image.Image' widget.
imageNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Image
    -- ^ __Returns:__ a newly created t'GI.Gtk.Objects.Image.Image' widget.
imageNew :: m Image
imageNew  = IO Image -> m Image
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Image -> m Image) -> IO Image -> m Image
forall a b. (a -> b) -> a -> b
$ do
    Ptr Image
result <- IO (Ptr Image)
gtk_image_new
    Text -> Ptr Image -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "imageNew" Ptr Image
result
    Image
result' <- ((ManagedPtr Image -> Image) -> Ptr Image -> IO Image
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Image -> Image
Image) Ptr Image
result
    Image -> IO Image
forall (m :: * -> *) a. Monad m => a -> m a
return Image
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Image::new_from_animation
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "animation"
--           , argType =
--               TInterface
--                 Name { namespace = "GdkPixbuf" , name = "PixbufAnimation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an animation" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Image" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_image_new_from_animation" gtk_image_new_from_animation :: 
    Ptr GdkPixbuf.PixbufAnimation.PixbufAnimation -> -- animation : TInterface (Name {namespace = "GdkPixbuf", name = "PixbufAnimation"})
    IO (Ptr Image)

-- | Creates a t'GI.Gtk.Objects.Image.Image' displaying the given animation.
-- The t'GI.Gtk.Objects.Image.Image' does not assume a reference to the
-- animation; you still need to unref it if you own references.
-- t'GI.Gtk.Objects.Image.Image' will add its own reference rather than adopting yours.
-- 
-- Note that the animation frames are shown using a timeout with
-- 'GI.GLib.Constants.PRIORITY_DEFAULT'. When using animations to indicate busyness,
-- keep in mind that the animation will only be shown if the main loop
-- is not busy with something that has a higher priority.
imageNewFromAnimation ::
    (B.CallStack.HasCallStack, MonadIO m, GdkPixbuf.PixbufAnimation.IsPixbufAnimation a) =>
    a
    -- ^ /@animation@/: an animation
    -> m Image
    -- ^ __Returns:__ a new t'GI.Gtk.Objects.Image.Image' widget
imageNewFromAnimation :: a -> m Image
imageNewFromAnimation animation :: a
animation = IO Image -> m Image
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Image -> m Image) -> IO Image -> m Image
forall a b. (a -> b) -> a -> b
$ do
    Ptr PixbufAnimation
animation' <- a -> IO (Ptr PixbufAnimation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
animation
    Ptr Image
result <- Ptr PixbufAnimation -> IO (Ptr Image)
gtk_image_new_from_animation Ptr PixbufAnimation
animation'
    Text -> Ptr Image -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "imageNewFromAnimation" Ptr Image
result
    Image
result' <- ((ManagedPtr Image -> Image) -> Ptr Image -> IO Image
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Image -> Image
Image) Ptr Image
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
animation
    Image -> IO Image
forall (m :: * -> *) a. Monad m => a -> m a
return Image
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Image::new_from_file
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "filename"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a filename" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Image" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_image_new_from_file" gtk_image_new_from_file :: 
    CString ->                              -- filename : TBasicType TFileName
    IO (Ptr Image)

-- | Creates a new t'GI.Gtk.Objects.Image.Image' displaying the file /@filename@/. If the file
-- isn’t found or can’t be loaded, the resulting t'GI.Gtk.Objects.Image.Image' will
-- display a “broken image” icon. This function never returns 'P.Nothing',
-- it always returns a valid t'GI.Gtk.Objects.Image.Image' widget.
-- 
-- If the file contains an animation, the image will contain an
-- animation.
-- 
-- If you need to detect failures to load the file, use
-- 'GI.GdkPixbuf.Objects.Pixbuf.pixbufNewFromFile' to load the file yourself, then create
-- the t'GI.Gtk.Objects.Image.Image' from the pixbuf. (Or for animations, use
-- 'GI.GdkPixbuf.Objects.PixbufAnimation.pixbufAnimationNewFromFile').
-- 
-- The storage type ('GI.Gtk.Objects.Image.imageGetStorageType') of the returned
-- image is not defined, it will be whatever is appropriate for
-- displaying the file.
imageNewFromFile ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    [Char]
    -- ^ /@filename@/: a filename
    -> m Image
    -- ^ __Returns:__ a new t'GI.Gtk.Objects.Image.Image'
imageNewFromFile :: String -> m Image
imageNewFromFile filename :: String
filename = IO Image -> m Image
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Image -> m Image) -> IO Image -> m Image
forall a b. (a -> b) -> a -> b
$ do
    CString
filename' <- String -> IO CString
stringToCString String
filename
    Ptr Image
result <- CString -> IO (Ptr Image)
gtk_image_new_from_file CString
filename'
    Text -> Ptr Image -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "imageNewFromFile" Ptr Image
result
    Image
result' <- ((ManagedPtr Image -> Image) -> Ptr Image -> IO Image
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Image -> Image
Image) Ptr Image
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
filename'
    Image -> IO Image
forall (m :: * -> *) a. Monad m => a -> m a
return Image
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Image::new_from_gicon
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "icon"
--           , argType = TInterface Name { namespace = "Gio" , name = "Icon" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an icon" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a stock icon size (#GtkIconSize)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Image" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_image_new_from_gicon" gtk_image_new_from_gicon :: 
    Ptr Gio.Icon.Icon ->                    -- icon : TInterface (Name {namespace = "Gio", name = "Icon"})
    Int32 ->                                -- size : TBasicType TInt
    IO (Ptr Image)

-- | Creates a t'GI.Gtk.Objects.Image.Image' displaying an icon from the current icon theme.
-- If the icon name isn’t known, a “broken image” icon will be
-- displayed instead.  If the current icon theme is changed, the icon
-- will be updated appropriately.
-- 
-- /Since: 2.14/
imageNewFromGicon ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.Icon.IsIcon a) =>
    a
    -- ^ /@icon@/: an icon
    -> Int32
    -- ^ /@size@/: a stock icon size (t'GI.Gtk.Enums.IconSize')
    -> m Image
    -- ^ __Returns:__ a new t'GI.Gtk.Objects.Image.Image' displaying the themed icon
imageNewFromGicon :: a -> Int32 -> m Image
imageNewFromGicon icon :: a
icon size :: Int32
size = IO Image -> m Image
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Image -> m Image) -> IO Image -> m Image
forall a b. (a -> b) -> a -> b
$ do
    Ptr Icon
icon' <- a -> IO (Ptr Icon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
icon
    Ptr Image
result <- Ptr Icon -> Int32 -> IO (Ptr Image)
gtk_image_new_from_gicon Ptr Icon
icon' Int32
size
    Text -> Ptr Image -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "imageNewFromGicon" Ptr Image
result
    Image
result' <- ((ManagedPtr Image -> Image) -> Ptr Image -> IO Image
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Image -> Image
Image) Ptr Image
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
icon
    Image -> IO Image
forall (m :: * -> *) a. Monad m => a -> m a
return Image
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Image::new_from_icon_name
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "icon_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an icon name or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a stock icon size (#GtkIconSize)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Image" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_image_new_from_icon_name" gtk_image_new_from_icon_name :: 
    CString ->                              -- icon_name : TBasicType TUTF8
    Int32 ->                                -- size : TBasicType TInt
    IO (Ptr Image)

-- | Creates a t'GI.Gtk.Objects.Image.Image' displaying an icon from the current icon theme.
-- If the icon name isn’t known, a “broken image” icon will be
-- displayed instead.  If the current icon theme is changed, the icon
-- will be updated appropriately.
-- 
-- /Since: 2.6/
imageNewFromIconName ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Maybe (T.Text)
    -- ^ /@iconName@/: an icon name or 'P.Nothing'
    -> Int32
    -- ^ /@size@/: a stock icon size (t'GI.Gtk.Enums.IconSize')
    -> m Image
    -- ^ __Returns:__ a new t'GI.Gtk.Objects.Image.Image' displaying the themed icon
imageNewFromIconName :: Maybe Text -> Int32 -> m Image
imageNewFromIconName iconName :: Maybe Text
iconName size :: Int32
size = IO Image -> m Image
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Image -> m Image) -> IO Image -> m Image
forall a b. (a -> b) -> a -> b
$ do
    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 Image
result <- CString -> Int32 -> IO (Ptr Image)
gtk_image_new_from_icon_name CString
maybeIconName Int32
size
    Text -> Ptr Image -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "imageNewFromIconName" Ptr Image
result
    Image
result' <- ((ManagedPtr Image -> Image) -> Ptr Image -> IO Image
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Image -> Image
Image) Ptr Image
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeIconName
    Image -> IO Image
forall (m :: * -> *) a. Monad m => a -> m a
return Image
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Image::new_from_icon_set
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "icon_set"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IconSet" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkIconSet" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a stock icon size (#GtkIconSize)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Image" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_image_new_from_icon_set" gtk_image_new_from_icon_set :: 
    Ptr Gtk.IconSet.IconSet ->              -- icon_set : TInterface (Name {namespace = "Gtk", name = "IconSet"})
    Int32 ->                                -- size : TBasicType TInt
    IO (Ptr Image)

{-# DEPRECATED imageNewFromIconSet ["(Since version 3.10)","Use 'GI.Gtk.Objects.Image.imageNewFromIconName' instead."] #-}
-- | Creates a t'GI.Gtk.Objects.Image.Image' displaying an icon set. Sample stock sizes are
-- @/GTK_ICON_SIZE_MENU/@, @/GTK_ICON_SIZE_SMALL_TOOLBAR/@. Instead of using
-- this function, usually it’s better to create a t'GI.Gtk.Objects.IconFactory.IconFactory', put
-- your icon sets in the icon factory, add the icon factory to the
-- list of default factories with 'GI.Gtk.Objects.IconFactory.iconFactoryAddDefault', and
-- then use 'GI.Gtk.Objects.Image.imageNewFromStock'. This will allow themes to
-- override the icon you ship with your application.
-- 
-- The t'GI.Gtk.Objects.Image.Image' does not assume a reference to the
-- icon set; you still need to unref it if you own references.
-- t'GI.Gtk.Objects.Image.Image' will add its own reference rather than adopting yours.
imageNewFromIconSet ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Gtk.IconSet.IconSet
    -- ^ /@iconSet@/: a t'GI.Gtk.Structs.IconSet.IconSet'
    -> Int32
    -- ^ /@size@/: a stock icon size (t'GI.Gtk.Enums.IconSize')
    -> m Image
    -- ^ __Returns:__ a new t'GI.Gtk.Objects.Image.Image'
imageNewFromIconSet :: IconSet -> Int32 -> m Image
imageNewFromIconSet iconSet :: IconSet
iconSet size :: Int32
size = IO Image -> m Image
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Image -> m Image) -> IO Image -> m Image
forall a b. (a -> b) -> a -> b
$ do
    Ptr IconSet
iconSet' <- IconSet -> IO (Ptr IconSet)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr IconSet
iconSet
    Ptr Image
result <- Ptr IconSet -> Int32 -> IO (Ptr Image)
gtk_image_new_from_icon_set Ptr IconSet
iconSet' Int32
size
    Text -> Ptr Image -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "imageNewFromIconSet" Ptr Image
result
    Image
result' <- ((ManagedPtr Image -> Image) -> Ptr Image -> IO Image
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Image -> Image
Image) Ptr Image
result
    IconSet -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr IconSet
iconSet
    Image -> IO Image
forall (m :: * -> *) a. Monad m => a -> m a
return Image
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Image::new_from_pixbuf
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "pixbuf"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkPixbuf, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Image" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_image_new_from_pixbuf" gtk_image_new_from_pixbuf :: 
    Ptr GdkPixbuf.Pixbuf.Pixbuf ->          -- pixbuf : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    IO (Ptr Image)

-- | Creates a new t'GI.Gtk.Objects.Image.Image' displaying /@pixbuf@/.
-- The t'GI.Gtk.Objects.Image.Image' does not assume a reference to the
-- pixbuf; you still need to unref it if you own references.
-- t'GI.Gtk.Objects.Image.Image' will add its own reference rather than adopting yours.
-- 
-- Note that this function just creates an t'GI.Gtk.Objects.Image.Image' from the pixbuf. The
-- t'GI.Gtk.Objects.Image.Image' created will not react to state changes. Should you want that,
-- you should use 'GI.Gtk.Objects.Image.imageNewFromIconName'.
imageNewFromPixbuf ::
    (B.CallStack.HasCallStack, MonadIO m, GdkPixbuf.Pixbuf.IsPixbuf a) =>
    Maybe (a)
    -- ^ /@pixbuf@/: a t'GI.GdkPixbuf.Objects.Pixbuf.Pixbuf', or 'P.Nothing'
    -> m Image
    -- ^ __Returns:__ a new t'GI.Gtk.Objects.Image.Image'
imageNewFromPixbuf :: Maybe a -> m Image
imageNewFromPixbuf pixbuf :: Maybe a
pixbuf = IO Image -> m Image
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Image -> m Image) -> IO Image -> m Image
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pixbuf
maybePixbuf <- case Maybe a
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 :: a
jPixbuf -> do
            Ptr Pixbuf
jPixbuf' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jPixbuf
            Ptr Pixbuf -> IO (Ptr Pixbuf)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Pixbuf
jPixbuf'
    Ptr Image
result <- Ptr Pixbuf -> IO (Ptr Image)
gtk_image_new_from_pixbuf Ptr Pixbuf
maybePixbuf
    Text -> Ptr Image -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "imageNewFromPixbuf" Ptr Image
result
    Image
result' <- ((ManagedPtr Image -> Image) -> Ptr Image -> IO Image
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Image -> Image
Image) Ptr Image
result
    Maybe a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
pixbuf a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Image -> IO Image
forall (m :: * -> *) a. Monad m => a -> m a
return Image
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Image::new_from_resource
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "resource_path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a resource path" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Image" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_image_new_from_resource" gtk_image_new_from_resource :: 
    CString ->                              -- resource_path : TBasicType TUTF8
    IO (Ptr Image)

-- | Creates a new t'GI.Gtk.Objects.Image.Image' displaying the resource file /@resourcePath@/. If the file
-- isn’t found or can’t be loaded, the resulting t'GI.Gtk.Objects.Image.Image' will
-- display a “broken image” icon. This function never returns 'P.Nothing',
-- it always returns a valid t'GI.Gtk.Objects.Image.Image' widget.
-- 
-- If the file contains an animation, the image will contain an
-- animation.
-- 
-- If you need to detect failures to load the file, use
-- 'GI.GdkPixbuf.Objects.Pixbuf.pixbufNewFromFile' to load the file yourself, then create
-- the t'GI.Gtk.Objects.Image.Image' from the pixbuf. (Or for animations, use
-- 'GI.GdkPixbuf.Objects.PixbufAnimation.pixbufAnimationNewFromFile').
-- 
-- The storage type ('GI.Gtk.Objects.Image.imageGetStorageType') of the returned
-- image is not defined, it will be whatever is appropriate for
-- displaying the file.
-- 
-- /Since: 3.4/
imageNewFromResource ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@resourcePath@/: a resource path
    -> m Image
    -- ^ __Returns:__ a new t'GI.Gtk.Objects.Image.Image'
imageNewFromResource :: Text -> m Image
imageNewFromResource resourcePath :: Text
resourcePath = IO Image -> m Image
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Image -> m Image) -> IO Image -> m Image
forall a b. (a -> b) -> a -> b
$ do
    CString
resourcePath' <- Text -> IO CString
textToCString Text
resourcePath
    Ptr Image
result <- CString -> IO (Ptr Image)
gtk_image_new_from_resource CString
resourcePath'
    Text -> Ptr Image -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "imageNewFromResource" Ptr Image
result
    Image
result' <- ((ManagedPtr Image -> Image) -> Ptr Image -> IO Image
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Image -> Image
Image) Ptr Image
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
resourcePath'
    Image -> IO Image
forall (m :: * -> *) a. Monad m => a -> m a
return Image
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Image::new_from_stock
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "stock_id"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a stock icon name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a stock icon size (#GtkIconSize)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Image" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_image_new_from_stock" gtk_image_new_from_stock :: 
    CString ->                              -- stock_id : TBasicType TUTF8
    Int32 ->                                -- size : TBasicType TInt
    IO (Ptr Image)

{-# DEPRECATED imageNewFromStock ["(Since version 3.10)","Use 'GI.Gtk.Objects.Image.imageNewFromIconName' instead."] #-}
-- | Creates a t'GI.Gtk.Objects.Image.Image' displaying a stock icon. Sample stock icon
-- names are 'GI.Gtk.Constants.STOCK_OPEN', 'GI.Gtk.Constants.STOCK_QUIT'. Sample stock sizes
-- are @/GTK_ICON_SIZE_MENU/@, @/GTK_ICON_SIZE_SMALL_TOOLBAR/@. If the stock
-- icon name isn’t known, the image will be empty.
-- You can register your own stock icon names, see
-- 'GI.Gtk.Objects.IconFactory.iconFactoryAddDefault' and 'GI.Gtk.Objects.IconFactory.iconFactoryAdd'.
imageNewFromStock ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@stockId@/: a stock icon name
    -> Int32
    -- ^ /@size@/: a stock icon size (t'GI.Gtk.Enums.IconSize')
    -> m Image
    -- ^ __Returns:__ a new t'GI.Gtk.Objects.Image.Image' displaying the stock icon
imageNewFromStock :: Text -> Int32 -> m Image
imageNewFromStock stockId :: Text
stockId size :: Int32
size = IO Image -> m Image
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Image -> m Image) -> IO Image -> m Image
forall a b. (a -> b) -> a -> b
$ do
    CString
stockId' <- Text -> IO CString
textToCString Text
stockId
    Ptr Image
result <- CString -> Int32 -> IO (Ptr Image)
gtk_image_new_from_stock CString
stockId' Int32
size
    Text -> Ptr Image -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "imageNewFromStock" Ptr Image
result
    Image
result' <- ((ManagedPtr Image -> Image) -> Ptr Image -> IO Image
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Image -> Image
Image) Ptr Image
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
stockId'
    Image -> IO Image
forall (m :: * -> *) a. Monad m => a -> m a
return Image
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Image::new_from_surface
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "surface"
--           , argType =
--               TInterface Name { namespace = "cairo" , name = "Surface" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #cairo_surface_t, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Image" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_image_new_from_surface" gtk_image_new_from_surface :: 
    Ptr Cairo.Surface.Surface ->            -- surface : TInterface (Name {namespace = "cairo", name = "Surface"})
    IO (Ptr Image)

-- | Creates a new t'GI.Gtk.Objects.Image.Image' displaying /@surface@/.
-- The t'GI.Gtk.Objects.Image.Image' does not assume a reference to the
-- surface; you still need to unref it if you own references.
-- t'GI.Gtk.Objects.Image.Image' will add its own reference rather than adopting yours.
-- 
-- /Since: 3.10/
imageNewFromSurface ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Maybe (Cairo.Surface.Surface)
    -- ^ /@surface@/: a t'GI.Cairo.Structs.Surface.Surface', or 'P.Nothing'
    -> m Image
    -- ^ __Returns:__ a new t'GI.Gtk.Objects.Image.Image'
imageNewFromSurface :: Maybe Surface -> m Image
imageNewFromSurface surface :: Maybe Surface
surface = IO Image -> m Image
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Image -> m Image) -> IO Image -> m Image
forall a b. (a -> b) -> a -> b
$ do
    Ptr Surface
maybeSurface <- case Maybe Surface
surface of
        Nothing -> Ptr Surface -> IO (Ptr Surface)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Surface
forall a. Ptr a
nullPtr
        Just jSurface :: Surface
jSurface -> do
            Ptr Surface
jSurface' <- Surface -> IO (Ptr Surface)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Surface
jSurface
            Ptr Surface -> IO (Ptr Surface)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Surface
jSurface'
    Ptr Image
result <- Ptr Surface -> IO (Ptr Image)
gtk_image_new_from_surface Ptr Surface
maybeSurface
    Text -> Ptr Image -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "imageNewFromSurface" Ptr Image
result
    Image
result' <- ((ManagedPtr Image -> Image) -> Ptr Image -> IO Image
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Image -> Image
Image) Ptr Image
result
    Maybe Surface -> (Surface -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe Surface
surface Surface -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Image -> IO Image
forall (m :: * -> *) a. Monad m => a -> m a
return Image
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Image::clear
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "image"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Image" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkImage" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_image_clear" gtk_image_clear :: 
    Ptr Image ->                            -- image : TInterface (Name {namespace = "Gtk", name = "Image"})
    IO ()

-- | Resets the image to be empty.
-- 
-- /Since: 2.8/
imageClear ::
    (B.CallStack.HasCallStack, MonadIO m, IsImage a) =>
    a
    -- ^ /@image@/: a t'GI.Gtk.Objects.Image.Image'
    -> m ()
imageClear :: a -> m ()
imageClear image :: a
image = 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 Image
image' <- a -> IO (Ptr Image)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
image
    Ptr Image -> IO ()
gtk_image_clear Ptr Image
image'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
image
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ImageClearMethodInfo
instance (signature ~ (m ()), MonadIO m, IsImage a) => O.MethodInfo ImageClearMethodInfo a signature where
    overloadedMethod = imageClear

#endif

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

foreign import ccall "gtk_image_get_animation" gtk_image_get_animation :: 
    Ptr Image ->                            -- image : TInterface (Name {namespace = "Gtk", name = "Image"})
    IO (Ptr GdkPixbuf.PixbufAnimation.PixbufAnimation)

-- | Gets the t'GI.GdkPixbuf.Objects.PixbufAnimation.PixbufAnimation' being displayed by the t'GI.Gtk.Objects.Image.Image'.
-- The storage type of the image must be 'GI.Gtk.Enums.ImageTypeEmpty' or
-- 'GI.Gtk.Enums.ImageTypeAnimation' (see 'GI.Gtk.Objects.Image.imageGetStorageType').
-- The caller of this function does not own a reference to the
-- returned animation.
imageGetAnimation ::
    (B.CallStack.HasCallStack, MonadIO m, IsImage a) =>
    a
    -- ^ /@image@/: a t'GI.Gtk.Objects.Image.Image'
    -> m (Maybe GdkPixbuf.PixbufAnimation.PixbufAnimation)
    -- ^ __Returns:__ the displayed animation, or 'P.Nothing' if
    -- the image is empty
imageGetAnimation :: a -> m (Maybe PixbufAnimation)
imageGetAnimation image :: a
image = IO (Maybe PixbufAnimation) -> m (Maybe PixbufAnimation)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe PixbufAnimation) -> m (Maybe PixbufAnimation))
-> IO (Maybe PixbufAnimation) -> m (Maybe PixbufAnimation)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Image
image' <- a -> IO (Ptr Image)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
image
    Ptr PixbufAnimation
result <- Ptr Image -> IO (Ptr PixbufAnimation)
gtk_image_get_animation Ptr Image
image'
    Maybe PixbufAnimation
maybeResult <- Ptr PixbufAnimation
-> (Ptr PixbufAnimation -> IO PixbufAnimation)
-> IO (Maybe PixbufAnimation)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr PixbufAnimation
result ((Ptr PixbufAnimation -> IO PixbufAnimation)
 -> IO (Maybe PixbufAnimation))
-> (Ptr PixbufAnimation -> IO PixbufAnimation)
-> IO (Maybe PixbufAnimation)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr PixbufAnimation
result' -> do
        PixbufAnimation
result'' <- ((ManagedPtr PixbufAnimation -> PixbufAnimation)
-> Ptr PixbufAnimation -> IO PixbufAnimation
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr PixbufAnimation -> PixbufAnimation
GdkPixbuf.PixbufAnimation.PixbufAnimation) Ptr PixbufAnimation
result'
        PixbufAnimation -> IO PixbufAnimation
forall (m :: * -> *) a. Monad m => a -> m a
return PixbufAnimation
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
image
    Maybe PixbufAnimation -> IO (Maybe PixbufAnimation)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe PixbufAnimation
maybeResult

#if defined(ENABLE_OVERLOADING)
data ImageGetAnimationMethodInfo
instance (signature ~ (m (Maybe GdkPixbuf.PixbufAnimation.PixbufAnimation)), MonadIO m, IsImage a) => O.MethodInfo ImageGetAnimationMethodInfo a signature where
    overloadedMethod = imageGetAnimation

#endif

-- method Image::get_gicon
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "image"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Image" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkImage" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "gicon"
--           , argType = TInterface Name { namespace = "Gio" , name = "Icon" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "place to store a\n    #GIcon, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "place to store an icon size\n    (#GtkIconSize), or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_image_get_gicon" gtk_image_get_gicon :: 
    Ptr Image ->                            -- image : TInterface (Name {namespace = "Gtk", name = "Image"})
    Ptr (Ptr Gio.Icon.Icon) ->              -- gicon : TInterface (Name {namespace = "Gio", name = "Icon"})
    Ptr Int32 ->                            -- size : TBasicType TInt
    IO ()

-- | Gets the t'GI.Gio.Interfaces.Icon.Icon' and size being displayed by the t'GI.Gtk.Objects.Image.Image'.
-- The storage type of the image must be 'GI.Gtk.Enums.ImageTypeEmpty' or
-- 'GI.Gtk.Enums.ImageTypeGicon' (see 'GI.Gtk.Objects.Image.imageGetStorageType').
-- The caller of this function does not own a reference to the
-- returned t'GI.Gio.Interfaces.Icon.Icon'.
-- 
-- /Since: 2.14/
imageGetGicon ::
    (B.CallStack.HasCallStack, MonadIO m, IsImage a) =>
    a
    -- ^ /@image@/: a t'GI.Gtk.Objects.Image.Image'
    -> m ((Gio.Icon.Icon, Int32))
imageGetGicon :: a -> m (Icon, Int32)
imageGetGicon image :: a
image = IO (Icon, Int32) -> m (Icon, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Icon, Int32) -> m (Icon, Int32))
-> IO (Icon, Int32) -> m (Icon, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Image
image' <- a -> IO (Ptr Image)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
image
    Ptr (Ptr Icon)
gicon <- IO (Ptr (Ptr Icon))
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr (Ptr Gio.Icon.Icon))
    Ptr Int32
size <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Image -> Ptr (Ptr Icon) -> Ptr Int32 -> IO ()
gtk_image_get_gicon Ptr Image
image' Ptr (Ptr Icon)
gicon Ptr Int32
size
    Ptr Icon
gicon' <- Ptr (Ptr Icon) -> IO (Ptr Icon)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr Icon)
gicon
    Icon
gicon'' <- ((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
gicon'
    Int32
size' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
size
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
image
    Ptr (Ptr Icon) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr Icon)
gicon
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
size
    (Icon, Int32) -> IO (Icon, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Icon
gicon'', Int32
size')

#if defined(ENABLE_OVERLOADING)
data ImageGetGiconMethodInfo
instance (signature ~ (m ((Gio.Icon.Icon, Int32))), MonadIO m, IsImage a) => O.MethodInfo ImageGetGiconMethodInfo a signature where
    overloadedMethod = imageGetGicon

#endif

-- method Image::get_icon_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "image"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Image" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkImage" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "icon_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "place to store an\n    icon name, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "place to store an icon size\n    (#GtkIconSize), or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_image_get_icon_name" gtk_image_get_icon_name :: 
    Ptr Image ->                            -- image : TInterface (Name {namespace = "Gtk", name = "Image"})
    Ptr CString ->                          -- icon_name : TBasicType TUTF8
    Ptr Int32 ->                            -- size : TBasicType TInt
    IO ()

-- | Gets the icon name and size being displayed by the t'GI.Gtk.Objects.Image.Image'.
-- The storage type of the image must be 'GI.Gtk.Enums.ImageTypeEmpty' or
-- 'GI.Gtk.Enums.ImageTypeIconName' (see 'GI.Gtk.Objects.Image.imageGetStorageType').
-- The returned string is owned by the t'GI.Gtk.Objects.Image.Image' and should not
-- be freed.
-- 
-- /Since: 2.6/
imageGetIconName ::
    (B.CallStack.HasCallStack, MonadIO m, IsImage a) =>
    a
    -- ^ /@image@/: a t'GI.Gtk.Objects.Image.Image'
    -> m ((T.Text, Int32))
imageGetIconName :: a -> m (Text, Int32)
imageGetIconName image :: a
image = IO (Text, Int32) -> m (Text, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Text, Int32) -> m (Text, Int32))
-> IO (Text, Int32) -> m (Text, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Image
image' <- a -> IO (Ptr Image)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
image
    Ptr CString
iconName <- IO (Ptr CString)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CString)
    Ptr Int32
size <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Image -> Ptr CString -> Ptr Int32 -> IO ()
gtk_image_get_icon_name Ptr Image
image' Ptr CString
iconName Ptr Int32
size
    CString
iconName' <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek Ptr CString
iconName
    Text
iconName'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
iconName'
    Int32
size' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
size
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
image
    Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
iconName
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
size
    (Text, Int32) -> IO (Text, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Text
iconName'', Int32
size')

#if defined(ENABLE_OVERLOADING)
data ImageGetIconNameMethodInfo
instance (signature ~ (m ((T.Text, Int32))), MonadIO m, IsImage a) => O.MethodInfo ImageGetIconNameMethodInfo a signature where
    overloadedMethod = imageGetIconName

#endif

-- method Image::get_icon_set
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "image"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Image" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkImage" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "icon_set"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IconSet" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "location to store a\n    #GtkIconSet, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "location to store a stock\n    icon size (#GtkIconSize), or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_image_get_icon_set" gtk_image_get_icon_set :: 
    Ptr Image ->                            -- image : TInterface (Name {namespace = "Gtk", name = "Image"})
    Ptr (Ptr Gtk.IconSet.IconSet) ->        -- icon_set : TInterface (Name {namespace = "Gtk", name = "IconSet"})
    Ptr Int32 ->                            -- size : TBasicType TInt
    IO ()

{-# DEPRECATED imageGetIconSet ["(Since version 3.10)","Use 'GI.Gtk.Objects.Image.imageGetIconName' instead."] #-}
-- | Gets the icon set and size being displayed by the t'GI.Gtk.Objects.Image.Image'.
-- The storage type of the image must be 'GI.Gtk.Enums.ImageTypeEmpty' or
-- 'GI.Gtk.Enums.ImageTypeIconSet' (see 'GI.Gtk.Objects.Image.imageGetStorageType').
imageGetIconSet ::
    (B.CallStack.HasCallStack, MonadIO m, IsImage a) =>
    a
    -- ^ /@image@/: a t'GI.Gtk.Objects.Image.Image'
    -> m ((Gtk.IconSet.IconSet, Int32))
imageGetIconSet :: a -> m (IconSet, Int32)
imageGetIconSet image :: a
image = IO (IconSet, Int32) -> m (IconSet, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (IconSet, Int32) -> m (IconSet, Int32))
-> IO (IconSet, Int32) -> m (IconSet, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Image
image' <- a -> IO (Ptr Image)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
image
    Ptr (Ptr IconSet)
iconSet <- IO (Ptr (Ptr IconSet))
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr (Ptr Gtk.IconSet.IconSet))
    Ptr Int32
size <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Image -> Ptr (Ptr IconSet) -> Ptr Int32 -> IO ()
gtk_image_get_icon_set Ptr Image
image' Ptr (Ptr IconSet)
iconSet Ptr Int32
size
    Ptr IconSet
iconSet' <- Ptr (Ptr IconSet) -> IO (Ptr IconSet)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr IconSet)
iconSet
    IconSet
iconSet'' <- ((ManagedPtr IconSet -> IconSet) -> Ptr IconSet -> IO IconSet
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr IconSet -> IconSet
Gtk.IconSet.IconSet) Ptr IconSet
iconSet'
    Int32
size' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
size
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
image
    Ptr (Ptr IconSet) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr IconSet)
iconSet
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
size
    (IconSet, Int32) -> IO (IconSet, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (IconSet
iconSet'', Int32
size')

#if defined(ENABLE_OVERLOADING)
data ImageGetIconSetMethodInfo
instance (signature ~ (m ((Gtk.IconSet.IconSet, Int32))), MonadIO m, IsImage a) => O.MethodInfo ImageGetIconSetMethodInfo a signature where
    overloadedMethod = imageGetIconSet

#endif

-- method Image::get_pixbuf
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "image"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Image" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkImage" , 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_image_get_pixbuf" gtk_image_get_pixbuf :: 
    Ptr Image ->                            -- image : TInterface (Name {namespace = "Gtk", name = "Image"})
    IO (Ptr GdkPixbuf.Pixbuf.Pixbuf)

-- | Gets the t'GI.GdkPixbuf.Objects.Pixbuf.Pixbuf' being displayed by the t'GI.Gtk.Objects.Image.Image'.
-- The storage type of the image must be 'GI.Gtk.Enums.ImageTypeEmpty' or
-- 'GI.Gtk.Enums.ImageTypePixbuf' (see 'GI.Gtk.Objects.Image.imageGetStorageType').
-- The caller of this function does not own a reference to the
-- returned pixbuf.
imageGetPixbuf ::
    (B.CallStack.HasCallStack, MonadIO m, IsImage a) =>
    a
    -- ^ /@image@/: a t'GI.Gtk.Objects.Image.Image'
    -> m (Maybe GdkPixbuf.Pixbuf.Pixbuf)
    -- ^ __Returns:__ the displayed pixbuf, or 'P.Nothing' if
    -- the image is empty
imageGetPixbuf :: a -> m (Maybe Pixbuf)
imageGetPixbuf image :: a
image = IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Pixbuf) -> m (Maybe Pixbuf))
-> IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Image
image' <- a -> IO (Ptr Image)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
image
    Ptr Pixbuf
result <- Ptr Image -> IO (Ptr Pixbuf)
gtk_image_get_pixbuf Ptr Image
image'
    Maybe Pixbuf
maybeResult <- Ptr Pixbuf -> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Pixbuf
result ((Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf))
-> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr Pixbuf
result' -> do
        Pixbuf
result'' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Pixbuf -> Pixbuf
GdkPixbuf.Pixbuf.Pixbuf) Ptr Pixbuf
result'
        Pixbuf -> IO Pixbuf
forall (m :: * -> *) a. Monad m => a -> m a
return Pixbuf
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
image
    Maybe Pixbuf -> IO (Maybe Pixbuf)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Pixbuf
maybeResult

#if defined(ENABLE_OVERLOADING)
data ImageGetPixbufMethodInfo
instance (signature ~ (m (Maybe GdkPixbuf.Pixbuf.Pixbuf)), MonadIO m, IsImage a) => O.MethodInfo ImageGetPixbufMethodInfo a signature where
    overloadedMethod = imageGetPixbuf

#endif

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

foreign import ccall "gtk_image_get_pixel_size" gtk_image_get_pixel_size :: 
    Ptr Image ->                            -- image : TInterface (Name {namespace = "Gtk", name = "Image"})
    IO Int32

-- | Gets the pixel size used for named icons.
-- 
-- /Since: 2.6/
imageGetPixelSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsImage a) =>
    a
    -- ^ /@image@/: a t'GI.Gtk.Objects.Image.Image'
    -> m Int32
    -- ^ __Returns:__ the pixel size used for named icons.
imageGetPixelSize :: a -> m Int32
imageGetPixelSize image :: a
image = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Image
image' <- a -> IO (Ptr Image)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
image
    Int32
result <- Ptr Image -> IO Int32
gtk_image_get_pixel_size Ptr Image
image'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
image
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data ImageGetPixelSizeMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsImage a) => O.MethodInfo ImageGetPixelSizeMethodInfo a signature where
    overloadedMethod = imageGetPixelSize

#endif

-- method Image::get_stock
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "image"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Image" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkImage" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "stock_id"
--           , argType = TBasicType TUTF8
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "place to store a\n    stock icon name, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "place to store a stock icon\n    size (#GtkIconSize), or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_image_get_stock" gtk_image_get_stock :: 
    Ptr Image ->                            -- image : TInterface (Name {namespace = "Gtk", name = "Image"})
    Ptr CString ->                          -- stock_id : TBasicType TUTF8
    Ptr Int32 ->                            -- size : TBasicType TInt
    IO ()

{-# DEPRECATED imageGetStock ["(Since version 3.10)","Use 'GI.Gtk.Objects.Image.imageGetIconName' instead."] #-}
-- | Gets the stock icon name and size being displayed by the t'GI.Gtk.Objects.Image.Image'.
-- The storage type of the image must be 'GI.Gtk.Enums.ImageTypeEmpty' or
-- 'GI.Gtk.Enums.ImageTypeStock' (see 'GI.Gtk.Objects.Image.imageGetStorageType').
-- The returned string is owned by the t'GI.Gtk.Objects.Image.Image' and should not
-- be freed.
imageGetStock ::
    (B.CallStack.HasCallStack, MonadIO m, IsImage a) =>
    a
    -- ^ /@image@/: a t'GI.Gtk.Objects.Image.Image'
    -> m ((T.Text, Int32))
imageGetStock :: a -> m (Text, Int32)
imageGetStock image :: a
image = IO (Text, Int32) -> m (Text, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Text, Int32) -> m (Text, Int32))
-> IO (Text, Int32) -> m (Text, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Image
image' <- a -> IO (Ptr Image)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
image
    Ptr CString
stockId <- IO (Ptr CString)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CString)
    Ptr Int32
size <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Image -> Ptr CString -> Ptr Int32 -> IO ()
gtk_image_get_stock Ptr Image
image' Ptr CString
stockId Ptr Int32
size
    CString
stockId' <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek Ptr CString
stockId
    Text
stockId'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
stockId'
    Int32
size' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
size
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
image
    Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
stockId
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
size
    (Text, Int32) -> IO (Text, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Text
stockId'', Int32
size')

#if defined(ENABLE_OVERLOADING)
data ImageGetStockMethodInfo
instance (signature ~ (m ((T.Text, Int32))), MonadIO m, IsImage a) => O.MethodInfo ImageGetStockMethodInfo a signature where
    overloadedMethod = imageGetStock

#endif

-- method Image::get_storage_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "image"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Image" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkImage" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "ImageType" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_image_get_storage_type" gtk_image_get_storage_type :: 
    Ptr Image ->                            -- image : TInterface (Name {namespace = "Gtk", name = "Image"})
    IO CUInt

-- | Gets the type of representation being used by the t'GI.Gtk.Objects.Image.Image'
-- to store image data. If the t'GI.Gtk.Objects.Image.Image' has no image data,
-- the return value will be 'GI.Gtk.Enums.ImageTypeEmpty'.
imageGetStorageType ::
    (B.CallStack.HasCallStack, MonadIO m, IsImage a) =>
    a
    -- ^ /@image@/: a t'GI.Gtk.Objects.Image.Image'
    -> m Gtk.Enums.ImageType
    -- ^ __Returns:__ image representation being used
imageGetStorageType :: a -> m ImageType
imageGetStorageType image :: a
image = IO ImageType -> m ImageType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ImageType -> m ImageType) -> IO ImageType -> m ImageType
forall a b. (a -> b) -> a -> b
$ do
    Ptr Image
image' <- a -> IO (Ptr Image)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
image
    CUInt
result <- Ptr Image -> IO CUInt
gtk_image_get_storage_type Ptr Image
image'
    let result' :: ImageType
result' = (Int -> ImageType
forall a. Enum a => Int -> a
toEnum (Int -> ImageType) -> (CUInt -> Int) -> CUInt -> ImageType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
image
    ImageType -> IO ImageType
forall (m :: * -> *) a. Monad m => a -> m a
return ImageType
result'

#if defined(ENABLE_OVERLOADING)
data ImageGetStorageTypeMethodInfo
instance (signature ~ (m Gtk.Enums.ImageType), MonadIO m, IsImage a) => O.MethodInfo ImageGetStorageTypeMethodInfo a signature where
    overloadedMethod = imageGetStorageType

#endif

-- method Image::set_from_animation
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "image"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Image" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkImage" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "animation"
--           , argType =
--               TInterface
--                 Name { namespace = "GdkPixbuf" , name = "PixbufAnimation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GdkPixbufAnimation"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_image_set_from_animation" gtk_image_set_from_animation :: 
    Ptr Image ->                            -- image : TInterface (Name {namespace = "Gtk", name = "Image"})
    Ptr GdkPixbuf.PixbufAnimation.PixbufAnimation -> -- animation : TInterface (Name {namespace = "GdkPixbuf", name = "PixbufAnimation"})
    IO ()

-- | Causes the t'GI.Gtk.Objects.Image.Image' to display the given animation (or display
-- nothing, if you set the animation to 'P.Nothing').
imageSetFromAnimation ::
    (B.CallStack.HasCallStack, MonadIO m, IsImage a, GdkPixbuf.PixbufAnimation.IsPixbufAnimation b) =>
    a
    -- ^ /@image@/: a t'GI.Gtk.Objects.Image.Image'
    -> b
    -- ^ /@animation@/: the t'GI.GdkPixbuf.Objects.PixbufAnimation.PixbufAnimation'
    -> m ()
imageSetFromAnimation :: a -> b -> m ()
imageSetFromAnimation image :: a
image animation :: b
animation = 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 Image
image' <- a -> IO (Ptr Image)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
image
    Ptr PixbufAnimation
animation' <- b -> IO (Ptr PixbufAnimation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
animation
    Ptr Image -> Ptr PixbufAnimation -> IO ()
gtk_image_set_from_animation Ptr Image
image' Ptr PixbufAnimation
animation'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
image
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
animation
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ImageSetFromAnimationMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsImage a, GdkPixbuf.PixbufAnimation.IsPixbufAnimation b) => O.MethodInfo ImageSetFromAnimationMethodInfo a signature where
    overloadedMethod = imageSetFromAnimation

#endif

-- method Image::set_from_file
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "image"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Image" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkImage" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "filename"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a filename 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_image_set_from_file" gtk_image_set_from_file :: 
    Ptr Image ->                            -- image : TInterface (Name {namespace = "Gtk", name = "Image"})
    CString ->                              -- filename : TBasicType TFileName
    IO ()

-- | See 'GI.Gtk.Objects.Image.imageNewFromFile' for details.
imageSetFromFile ::
    (B.CallStack.HasCallStack, MonadIO m, IsImage a) =>
    a
    -- ^ /@image@/: a t'GI.Gtk.Objects.Image.Image'
    -> Maybe ([Char])
    -- ^ /@filename@/: a filename or 'P.Nothing'
    -> m ()
imageSetFromFile :: a -> Maybe String -> m ()
imageSetFromFile image :: a
image filename :: Maybe String
filename = 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 Image
image' <- a -> IO (Ptr Image)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
image
    CString
maybeFilename <- case Maybe String
filename of
        Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just jFilename :: String
jFilename -> do
            CString
jFilename' <- String -> IO CString
stringToCString String
jFilename
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jFilename'
    Ptr Image -> CString -> IO ()
gtk_image_set_from_file Ptr Image
image' CString
maybeFilename
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
image
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeFilename
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ImageSetFromFileMethodInfo
instance (signature ~ (Maybe ([Char]) -> m ()), MonadIO m, IsImage a) => O.MethodInfo ImageSetFromFileMethodInfo a signature where
    overloadedMethod = imageSetFromFile

#endif

-- method Image::set_from_gicon
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "image"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Image" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkImage" , 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 = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an icon" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an icon size (#GtkIconSize)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_image_set_from_gicon" gtk_image_set_from_gicon :: 
    Ptr Image ->                            -- image : TInterface (Name {namespace = "Gtk", name = "Image"})
    Ptr Gio.Icon.Icon ->                    -- icon : TInterface (Name {namespace = "Gio", name = "Icon"})
    Int32 ->                                -- size : TBasicType TInt
    IO ()

-- | See 'GI.Gtk.Objects.Image.imageNewFromGicon' for details.
-- 
-- /Since: 2.14/
imageSetFromGicon ::
    (B.CallStack.HasCallStack, MonadIO m, IsImage a, Gio.Icon.IsIcon b) =>
    a
    -- ^ /@image@/: a t'GI.Gtk.Objects.Image.Image'
    -> b
    -- ^ /@icon@/: an icon
    -> Int32
    -- ^ /@size@/: an icon size (t'GI.Gtk.Enums.IconSize')
    -> m ()
imageSetFromGicon :: a -> b -> Int32 -> m ()
imageSetFromGicon image :: a
image icon :: b
icon size :: Int32
size = 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 Image
image' <- a -> IO (Ptr Image)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
image
    Ptr Icon
icon' <- b -> IO (Ptr Icon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
icon
    Ptr Image -> Ptr Icon -> Int32 -> IO ()
gtk_image_set_from_gicon Ptr Image
image' Ptr Icon
icon' Int32
size
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
image
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
icon
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ImageSetFromGiconMethodInfo
instance (signature ~ (b -> Int32 -> m ()), MonadIO m, IsImage a, Gio.Icon.IsIcon b) => O.MethodInfo ImageSetFromGiconMethodInfo a signature where
    overloadedMethod = imageSetFromGicon

#endif

-- method Image::set_from_icon_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "image"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Image" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkImage" , 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 "an icon name or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an icon size (#GtkIconSize)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_image_set_from_icon_name" gtk_image_set_from_icon_name :: 
    Ptr Image ->                            -- image : TInterface (Name {namespace = "Gtk", name = "Image"})
    CString ->                              -- icon_name : TBasicType TUTF8
    Int32 ->                                -- size : TBasicType TInt
    IO ()

-- | See 'GI.Gtk.Objects.Image.imageNewFromIconName' for details.
-- 
-- /Since: 2.6/
imageSetFromIconName ::
    (B.CallStack.HasCallStack, MonadIO m, IsImage a) =>
    a
    -- ^ /@image@/: a t'GI.Gtk.Objects.Image.Image'
    -> Maybe (T.Text)
    -- ^ /@iconName@/: an icon name or 'P.Nothing'
    -> Int32
    -- ^ /@size@/: an icon size (t'GI.Gtk.Enums.IconSize')
    -> m ()
imageSetFromIconName :: a -> Maybe Text -> Int32 -> m ()
imageSetFromIconName image :: a
image iconName :: Maybe Text
iconName size :: Int32
size = 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 Image
image' <- a -> IO (Ptr Image)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
image
    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 Image -> CString -> Int32 -> IO ()
gtk_image_set_from_icon_name Ptr Image
image' CString
maybeIconName Int32
size
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
image
    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 ImageSetFromIconNameMethodInfo
instance (signature ~ (Maybe (T.Text) -> Int32 -> m ()), MonadIO m, IsImage a) => O.MethodInfo ImageSetFromIconNameMethodInfo a signature where
    overloadedMethod = imageSetFromIconName

#endif

-- method Image::set_from_icon_set
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "image"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Image" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkImage" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "icon_set"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IconSet" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkIconSet" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a stock icon size (#GtkIconSize)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_image_set_from_icon_set" gtk_image_set_from_icon_set :: 
    Ptr Image ->                            -- image : TInterface (Name {namespace = "Gtk", name = "Image"})
    Ptr Gtk.IconSet.IconSet ->              -- icon_set : TInterface (Name {namespace = "Gtk", name = "IconSet"})
    Int32 ->                                -- size : TBasicType TInt
    IO ()

{-# DEPRECATED imageSetFromIconSet ["(Since version 3.10)","Use 'GI.Gtk.Objects.Image.imageSetFromIconName' instead."] #-}
-- | See 'GI.Gtk.Objects.Image.imageNewFromIconSet' for details.
imageSetFromIconSet ::
    (B.CallStack.HasCallStack, MonadIO m, IsImage a) =>
    a
    -- ^ /@image@/: a t'GI.Gtk.Objects.Image.Image'
    -> Gtk.IconSet.IconSet
    -- ^ /@iconSet@/: a t'GI.Gtk.Structs.IconSet.IconSet'
    -> Int32
    -- ^ /@size@/: a stock icon size (t'GI.Gtk.Enums.IconSize')
    -> m ()
imageSetFromIconSet :: a -> IconSet -> Int32 -> m ()
imageSetFromIconSet image :: a
image iconSet :: IconSet
iconSet size :: Int32
size = 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 Image
image' <- a -> IO (Ptr Image)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
image
    Ptr IconSet
iconSet' <- IconSet -> IO (Ptr IconSet)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr IconSet
iconSet
    Ptr Image -> Ptr IconSet -> Int32 -> IO ()
gtk_image_set_from_icon_set Ptr Image
image' Ptr IconSet
iconSet' Int32
size
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
image
    IconSet -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr IconSet
iconSet
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ImageSetFromIconSetMethodInfo
instance (signature ~ (Gtk.IconSet.IconSet -> Int32 -> m ()), MonadIO m, IsImage a) => O.MethodInfo ImageSetFromIconSetMethodInfo a signature where
    overloadedMethod = imageSetFromIconSet

#endif

-- method Image::set_from_pixbuf
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "image"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Image" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkImage" , 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 "a #GdkPixbuf 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_image_set_from_pixbuf" gtk_image_set_from_pixbuf :: 
    Ptr Image ->                            -- image : TInterface (Name {namespace = "Gtk", name = "Image"})
    Ptr GdkPixbuf.Pixbuf.Pixbuf ->          -- pixbuf : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    IO ()

-- | See 'GI.Gtk.Objects.Image.imageNewFromPixbuf' for details.
imageSetFromPixbuf ::
    (B.CallStack.HasCallStack, MonadIO m, IsImage a, GdkPixbuf.Pixbuf.IsPixbuf b) =>
    a
    -- ^ /@image@/: a t'GI.Gtk.Objects.Image.Image'
    -> Maybe (b)
    -- ^ /@pixbuf@/: a t'GI.GdkPixbuf.Objects.Pixbuf.Pixbuf' or 'P.Nothing'
    -> m ()
imageSetFromPixbuf :: a -> Maybe b -> m ()
imageSetFromPixbuf image :: a
image 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 Image
image' <- a -> IO (Ptr Image)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
image
    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 Image -> Ptr Pixbuf -> IO ()
gtk_image_set_from_pixbuf Ptr Image
image' Ptr Pixbuf
maybePixbuf
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
image
    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 ImageSetFromPixbufMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsImage a, GdkPixbuf.Pixbuf.IsPixbuf b) => O.MethodInfo ImageSetFromPixbufMethodInfo a signature where
    overloadedMethod = imageSetFromPixbuf

#endif

-- method Image::set_from_resource
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "image"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Image" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkImage" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "resource_path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a resource path 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_image_set_from_resource" gtk_image_set_from_resource :: 
    Ptr Image ->                            -- image : TInterface (Name {namespace = "Gtk", name = "Image"})
    CString ->                              -- resource_path : TBasicType TUTF8
    IO ()

-- | See 'GI.Gtk.Objects.Image.imageNewFromResource' for details.
imageSetFromResource ::
    (B.CallStack.HasCallStack, MonadIO m, IsImage a) =>
    a
    -- ^ /@image@/: a t'GI.Gtk.Objects.Image.Image'
    -> Maybe (T.Text)
    -- ^ /@resourcePath@/: a resource path or 'P.Nothing'
    -> m ()
imageSetFromResource :: a -> Maybe Text -> m ()
imageSetFromResource image :: a
image resourcePath :: Maybe Text
resourcePath = 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 Image
image' <- a -> IO (Ptr Image)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
image
    CString
maybeResourcePath <- case Maybe Text
resourcePath of
        Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just jResourcePath :: Text
jResourcePath -> do
            CString
jResourcePath' <- Text -> IO CString
textToCString Text
jResourcePath
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jResourcePath'
    Ptr Image -> CString -> IO ()
gtk_image_set_from_resource Ptr Image
image' CString
maybeResourcePath
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
image
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeResourcePath
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

#endif

-- method Image::set_from_stock
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "image"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Image" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkImage" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "stock_id"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a stock icon name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a stock icon size (#GtkIconSize)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_image_set_from_stock" gtk_image_set_from_stock :: 
    Ptr Image ->                            -- image : TInterface (Name {namespace = "Gtk", name = "Image"})
    CString ->                              -- stock_id : TBasicType TUTF8
    Int32 ->                                -- size : TBasicType TInt
    IO ()

{-# DEPRECATED imageSetFromStock ["(Since version 3.10)","Use 'GI.Gtk.Objects.Image.imageSetFromIconName' instead."] #-}
-- | See 'GI.Gtk.Objects.Image.imageNewFromStock' for details.
imageSetFromStock ::
    (B.CallStack.HasCallStack, MonadIO m, IsImage a) =>
    a
    -- ^ /@image@/: a t'GI.Gtk.Objects.Image.Image'
    -> T.Text
    -- ^ /@stockId@/: a stock icon name
    -> Int32
    -- ^ /@size@/: a stock icon size (t'GI.Gtk.Enums.IconSize')
    -> m ()
imageSetFromStock :: a -> Text -> Int32 -> m ()
imageSetFromStock image :: a
image stockId :: Text
stockId size :: Int32
size = 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 Image
image' <- a -> IO (Ptr Image)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
image
    CString
stockId' <- Text -> IO CString
textToCString Text
stockId
    Ptr Image -> CString -> Int32 -> IO ()
gtk_image_set_from_stock Ptr Image
image' CString
stockId' Int32
size
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
image
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
stockId'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ImageSetFromStockMethodInfo
instance (signature ~ (T.Text -> Int32 -> m ()), MonadIO m, IsImage a) => O.MethodInfo ImageSetFromStockMethodInfo a signature where
    overloadedMethod = imageSetFromStock

#endif

-- method Image::set_from_surface
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "image"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Image" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkImage" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "surface"
--           , argType =
--               TInterface Name { namespace = "cairo" , name = "Surface" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a cairo_surface_t 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_image_set_from_surface" gtk_image_set_from_surface :: 
    Ptr Image ->                            -- image : TInterface (Name {namespace = "Gtk", name = "Image"})
    Ptr Cairo.Surface.Surface ->            -- surface : TInterface (Name {namespace = "cairo", name = "Surface"})
    IO ()

-- | See 'GI.Gtk.Objects.Image.imageNewFromSurface' for details.
-- 
-- /Since: 3.10/
imageSetFromSurface ::
    (B.CallStack.HasCallStack, MonadIO m, IsImage a) =>
    a
    -- ^ /@image@/: a t'GI.Gtk.Objects.Image.Image'
    -> Maybe (Cairo.Surface.Surface)
    -- ^ /@surface@/: a cairo_surface_t or 'P.Nothing'
    -> m ()
imageSetFromSurface :: a -> Maybe Surface -> m ()
imageSetFromSurface image :: a
image surface :: Maybe Surface
surface = 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 Image
image' <- a -> IO (Ptr Image)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
image
    Ptr Surface
maybeSurface <- case Maybe Surface
surface of
        Nothing -> Ptr Surface -> IO (Ptr Surface)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Surface
forall a. Ptr a
nullPtr
        Just jSurface :: Surface
jSurface -> do
            Ptr Surface
jSurface' <- Surface -> IO (Ptr Surface)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Surface
jSurface
            Ptr Surface -> IO (Ptr Surface)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Surface
jSurface'
    Ptr Image -> Ptr Surface -> IO ()
gtk_image_set_from_surface Ptr Image
image' Ptr Surface
maybeSurface
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
image
    Maybe Surface -> (Surface -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe Surface
surface Surface -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ImageSetFromSurfaceMethodInfo
instance (signature ~ (Maybe (Cairo.Surface.Surface) -> m ()), MonadIO m, IsImage a) => O.MethodInfo ImageSetFromSurfaceMethodInfo a signature where
    overloadedMethod = imageSetFromSurface

#endif

-- method Image::set_pixel_size
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "image"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Image" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkImage" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pixel_size"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new pixel size" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_image_set_pixel_size" gtk_image_set_pixel_size :: 
    Ptr Image ->                            -- image : TInterface (Name {namespace = "Gtk", name = "Image"})
    Int32 ->                                -- pixel_size : TBasicType TInt
    IO ()

-- | Sets the pixel size to use for named icons. If the pixel size is set
-- to a value != -1, it is used instead of the icon size set by
-- 'GI.Gtk.Objects.Image.imageSetFromIconName'.
-- 
-- /Since: 2.6/
imageSetPixelSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsImage a) =>
    a
    -- ^ /@image@/: a t'GI.Gtk.Objects.Image.Image'
    -> Int32
    -- ^ /@pixelSize@/: the new pixel size
    -> m ()
imageSetPixelSize :: a -> Int32 -> m ()
imageSetPixelSize image :: a
image pixelSize :: Int32
pixelSize = 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 Image
image' <- a -> IO (Ptr Image)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
image
    Ptr Image -> Int32 -> IO ()
gtk_image_set_pixel_size Ptr Image
image' Int32
pixelSize
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
image
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ImageSetPixelSizeMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsImage a) => O.MethodInfo ImageSetPixelSizeMethodInfo a signature where
    overloadedMethod = imageSetPixelSize

#endif