{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Objects.Button
    ( 
    Button(..)                              ,
    IsButton                                ,
    toButton                                ,
 
#if defined(ENABLE_OVERLOADING)
    ResolveButtonMethod                     ,
#endif
#if defined(ENABLE_OVERLOADING)
    ButtonClickedMethodInfo                 ,
#endif
    buttonClicked                           ,
#if defined(ENABLE_OVERLOADING)
    ButtonEnterMethodInfo                   ,
#endif
    buttonEnter                             ,
#if defined(ENABLE_OVERLOADING)
    ButtonGetAlignmentMethodInfo            ,
#endif
    buttonGetAlignment                      ,
#if defined(ENABLE_OVERLOADING)
    ButtonGetAlwaysShowImageMethodInfo      ,
#endif
    buttonGetAlwaysShowImage                ,
#if defined(ENABLE_OVERLOADING)
    ButtonGetEventWindowMethodInfo          ,
#endif
    buttonGetEventWindow                    ,
#if defined(ENABLE_OVERLOADING)
    ButtonGetFocusOnClickMethodInfo         ,
#endif
    buttonGetFocusOnClick                   ,
#if defined(ENABLE_OVERLOADING)
    ButtonGetImageMethodInfo                ,
#endif
    buttonGetImage                          ,
#if defined(ENABLE_OVERLOADING)
    ButtonGetImagePositionMethodInfo        ,
#endif
    buttonGetImagePosition                  ,
#if defined(ENABLE_OVERLOADING)
    ButtonGetLabelMethodInfo                ,
#endif
    buttonGetLabel                          ,
#if defined(ENABLE_OVERLOADING)
    ButtonGetReliefMethodInfo               ,
#endif
    buttonGetRelief                         ,
#if defined(ENABLE_OVERLOADING)
    ButtonGetUseStockMethodInfo             ,
#endif
    buttonGetUseStock                       ,
#if defined(ENABLE_OVERLOADING)
    ButtonGetUseUnderlineMethodInfo         ,
#endif
    buttonGetUseUnderline                   ,
#if defined(ENABLE_OVERLOADING)
    ButtonLeaveMethodInfo                   ,
#endif
    buttonLeave                             ,
    buttonNew                               ,
    buttonNewFromIconName                   ,
    buttonNewFromStock                      ,
    buttonNewWithLabel                      ,
    buttonNewWithMnemonic                   ,
#if defined(ENABLE_OVERLOADING)
    ButtonPressedMethodInfo                 ,
#endif
    buttonPressed                           ,
#if defined(ENABLE_OVERLOADING)
    ButtonReleasedMethodInfo                ,
#endif
    buttonReleased                          ,
#if defined(ENABLE_OVERLOADING)
    ButtonSetAlignmentMethodInfo            ,
#endif
    buttonSetAlignment                      ,
#if defined(ENABLE_OVERLOADING)
    ButtonSetAlwaysShowImageMethodInfo      ,
#endif
    buttonSetAlwaysShowImage                ,
#if defined(ENABLE_OVERLOADING)
    ButtonSetFocusOnClickMethodInfo         ,
#endif
    buttonSetFocusOnClick                   ,
#if defined(ENABLE_OVERLOADING)
    ButtonSetImageMethodInfo                ,
#endif
    buttonSetImage                          ,
#if defined(ENABLE_OVERLOADING)
    ButtonSetImagePositionMethodInfo        ,
#endif
    buttonSetImagePosition                  ,
#if defined(ENABLE_OVERLOADING)
    ButtonSetLabelMethodInfo                ,
#endif
    buttonSetLabel                          ,
#if defined(ENABLE_OVERLOADING)
    ButtonSetReliefMethodInfo               ,
#endif
    buttonSetRelief                         ,
#if defined(ENABLE_OVERLOADING)
    ButtonSetUseStockMethodInfo             ,
#endif
    buttonSetUseStock                       ,
#if defined(ENABLE_OVERLOADING)
    ButtonSetUseUnderlineMethodInfo         ,
#endif
    buttonSetUseUnderline                   ,
 
#if defined(ENABLE_OVERLOADING)
    ButtonAlwaysShowImagePropertyInfo       ,
#endif
#if defined(ENABLE_OVERLOADING)
    buttonAlwaysShowImage                   ,
#endif
    constructButtonAlwaysShowImage          ,
    getButtonAlwaysShowImage                ,
    setButtonAlwaysShowImage                ,
#if defined(ENABLE_OVERLOADING)
    ButtonImagePropertyInfo                 ,
#endif
#if defined(ENABLE_OVERLOADING)
    buttonImage                             ,
#endif
    clearButtonImage                        ,
    constructButtonImage                    ,
    getButtonImage                          ,
    setButtonImage                          ,
#if defined(ENABLE_OVERLOADING)
    ButtonImagePositionPropertyInfo         ,
#endif
#if defined(ENABLE_OVERLOADING)
    buttonImagePosition                     ,
#endif
    constructButtonImagePosition            ,
    getButtonImagePosition                  ,
    setButtonImagePosition                  ,
#if defined(ENABLE_OVERLOADING)
    ButtonLabelPropertyInfo                 ,
#endif
#if defined(ENABLE_OVERLOADING)
    buttonLabel                             ,
#endif
    constructButtonLabel                    ,
    getButtonLabel                          ,
    setButtonLabel                          ,
#if defined(ENABLE_OVERLOADING)
    ButtonReliefPropertyInfo                ,
#endif
#if defined(ENABLE_OVERLOADING)
    buttonRelief                            ,
#endif
    constructButtonRelief                   ,
    getButtonRelief                         ,
    setButtonRelief                         ,
#if defined(ENABLE_OVERLOADING)
    ButtonUseStockPropertyInfo              ,
#endif
#if defined(ENABLE_OVERLOADING)
    buttonUseStock                          ,
#endif
    constructButtonUseStock                 ,
    getButtonUseStock                       ,
    setButtonUseStock                       ,
#if defined(ENABLE_OVERLOADING)
    ButtonUseUnderlinePropertyInfo          ,
#endif
#if defined(ENABLE_OVERLOADING)
    buttonUseUnderline                      ,
#endif
    constructButtonUseUnderline             ,
    getButtonUseUnderline                   ,
    setButtonUseUnderline                   ,
#if defined(ENABLE_OVERLOADING)
    ButtonXalignPropertyInfo                ,
#endif
#if defined(ENABLE_OVERLOADING)
    buttonXalign                            ,
#endif
    constructButtonXalign                   ,
    getButtonXalign                         ,
    setButtonXalign                         ,
#if defined(ENABLE_OVERLOADING)
    ButtonYalignPropertyInfo                ,
#endif
#if defined(ENABLE_OVERLOADING)
    buttonYalign                            ,
#endif
    constructButtonYalign                   ,
    getButtonYalign                         ,
    setButtonYalign                         ,
 
    ButtonActivateCallback                  ,
#if defined(ENABLE_OVERLOADING)
    ButtonActivateSignalInfo                ,
#endif
    C_ButtonActivateCallback                ,
    afterButtonActivate                     ,
    genClosure_ButtonActivate               ,
    mk_ButtonActivateCallback               ,
    noButtonActivateCallback                ,
    onButtonActivate                        ,
    wrap_ButtonActivateCallback             ,
    ButtonClickedCallback                   ,
#if defined(ENABLE_OVERLOADING)
    ButtonClickedSignalInfo                 ,
#endif
    C_ButtonClickedCallback                 ,
    afterButtonClicked                      ,
    genClosure_ButtonClicked                ,
    mk_ButtonClickedCallback                ,
    noButtonClickedCallback                 ,
    onButtonClicked                         ,
    wrap_ButtonClickedCallback              ,
    ButtonEnterCallback                     ,
#if defined(ENABLE_OVERLOADING)
    ButtonEnterSignalInfo                   ,
#endif
    C_ButtonEnterCallback                   ,
    afterButtonEnter                        ,
    genClosure_ButtonEnter                  ,
    mk_ButtonEnterCallback                  ,
    noButtonEnterCallback                   ,
    onButtonEnter                           ,
    wrap_ButtonEnterCallback                ,
    ButtonLeaveCallback                     ,
#if defined(ENABLE_OVERLOADING)
    ButtonLeaveSignalInfo                   ,
#endif
    C_ButtonLeaveCallback                   ,
    afterButtonLeave                        ,
    genClosure_ButtonLeave                  ,
    mk_ButtonLeaveCallback                  ,
    noButtonLeaveCallback                   ,
    onButtonLeave                           ,
    wrap_ButtonLeaveCallback                ,
    ButtonPressedCallback                   ,
#if defined(ENABLE_OVERLOADING)
    ButtonPressedSignalInfo                 ,
#endif
    C_ButtonPressedCallback                 ,
    afterButtonPressed                      ,
    genClosure_ButtonPressed                ,
    mk_ButtonPressedCallback                ,
    noButtonPressedCallback                 ,
    onButtonPressed                         ,
    wrap_ButtonPressedCallback              ,
    ButtonReleasedCallback                  ,
#if defined(ENABLE_OVERLOADING)
    ButtonReleasedSignalInfo                ,
#endif
    C_ButtonReleasedCallback                ,
    afterButtonReleased                     ,
    genClosure_ButtonReleased               ,
    mk_ButtonReleasedCallback               ,
    noButtonReleasedCallback                ,
    onButtonReleased                        ,
    wrap_ButtonReleasedCallback             ,
    ) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified GI.Atk.Interfaces.ImplementorIface as Atk.ImplementorIface
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Objects.Window as Gdk.Window
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Actionable as Gtk.Actionable
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Activatable as Gtk.Activatable
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Objects.Bin as Gtk.Bin
import {-# SOURCE #-} qualified GI.Gtk.Objects.Container as Gtk.Container
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget
newtype Button = Button (SP.ManagedPtr Button)
    deriving (Button -> Button -> Bool
(Button -> Button -> Bool)
-> (Button -> Button -> Bool) -> Eq Button
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Button -> Button -> Bool
$c/= :: Button -> Button -> Bool
== :: Button -> Button -> Bool
$c== :: Button -> Button -> Bool
Eq)
instance SP.ManagedPtrNewtype Button where
    toManagedPtr :: Button -> ManagedPtr Button
toManagedPtr (Button ManagedPtr Button
p) = ManagedPtr Button
p
foreign import ccall "gtk_button_get_type"
    c_gtk_button_get_type :: IO B.Types.GType
instance B.Types.TypedObject Button where
    glibType :: IO GType
glibType = IO GType
c_gtk_button_get_type
instance B.Types.GObject Button
class (SP.GObject o, O.IsDescendantOf Button o) => IsButton o
instance (SP.GObject o, O.IsDescendantOf Button o) => IsButton o
instance O.HasParentTypes Button
type instance O.ParentTypes Button = '[Gtk.Bin.Bin, Gtk.Container.Container, Gtk.Widget.Widget, GObject.Object.Object, Atk.ImplementorIface.ImplementorIface, Gtk.Actionable.Actionable, Gtk.Activatable.Activatable, Gtk.Buildable.Buildable]
toButton :: (MIO.MonadIO m, IsButton o) => o -> m Button
toButton :: forall (m :: * -> *) o. (MonadIO m, IsButton o) => o -> m Button
toButton = IO Button -> m Button
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Button -> m Button) -> (o -> IO Button) -> o -> m Button
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Button -> Button) -> o -> IO Button
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr Button -> Button
Button
instance B.GValue.IsGValue (Maybe Button) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_button_get_type
    gvalueSet_ :: Ptr GValue -> Maybe Button -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Button
P.Nothing = Ptr GValue -> Ptr Button -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Button
forall a. Ptr a
FP.nullPtr :: FP.Ptr Button)
    gvalueSet_ Ptr GValue
gv (P.Just Button
obj) = Button -> (Ptr Button -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Button
obj (Ptr GValue -> Ptr Button -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe Button)
gvalueGet_ Ptr GValue
gv = do
        Ptr Button
ptr <- Ptr GValue -> IO (Ptr Button)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Button)
        if Ptr Button
ptr Ptr Button -> Ptr Button -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Button
forall a. Ptr a
FP.nullPtr
        then Button -> Maybe Button
forall a. a -> Maybe a
P.Just (Button -> Maybe Button) -> IO Button -> IO (Maybe Button)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Button -> Button) -> Ptr Button -> IO Button
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Button -> Button
Button Ptr Button
ptr
        else Maybe Button -> IO (Maybe Button)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Button
forall a. Maybe a
P.Nothing
        
    
#if defined(ENABLE_OVERLOADING)
type family ResolveButtonMethod (t :: Symbol) (o :: *) :: * where
    ResolveButtonMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
    ResolveButtonMethod "add" o = Gtk.Container.ContainerAddMethodInfo
    ResolveButtonMethod "addAccelerator" o = Gtk.Widget.WidgetAddAcceleratorMethodInfo
    ResolveButtonMethod "addChild" o = Gtk.Buildable.BuildableAddChildMethodInfo
    ResolveButtonMethod "addDeviceEvents" o = Gtk.Widget.WidgetAddDeviceEventsMethodInfo
    ResolveButtonMethod "addEvents" o = Gtk.Widget.WidgetAddEventsMethodInfo
    ResolveButtonMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
    ResolveButtonMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
    ResolveButtonMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveButtonMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveButtonMethod "canActivateAccel" o = Gtk.Widget.WidgetCanActivateAccelMethodInfo
    ResolveButtonMethod "checkResize" o = Gtk.Container.ContainerCheckResizeMethodInfo
    ResolveButtonMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
    ResolveButtonMethod "childGetProperty" o = Gtk.Container.ContainerChildGetPropertyMethodInfo
    ResolveButtonMethod "childNotify" o = Gtk.Container.ContainerChildNotifyMethodInfo
    ResolveButtonMethod "childNotifyByPspec" o = Gtk.Container.ContainerChildNotifyByPspecMethodInfo
    ResolveButtonMethod "childSetProperty" o = Gtk.Container.ContainerChildSetPropertyMethodInfo
    ResolveButtonMethod "childType" o = Gtk.Container.ContainerChildTypeMethodInfo
    ResolveButtonMethod "classPath" o = Gtk.Widget.WidgetClassPathMethodInfo
    ResolveButtonMethod "clicked" o = ButtonClickedMethodInfo
    ResolveButtonMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
    ResolveButtonMethod "constructChild" o = Gtk.Buildable.BuildableConstructChildMethodInfo
    ResolveButtonMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
    ResolveButtonMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
    ResolveButtonMethod "customFinished" o = Gtk.Buildable.BuildableCustomFinishedMethodInfo
    ResolveButtonMethod "customTagEnd" o = Gtk.Buildable.BuildableCustomTagEndMethodInfo
    ResolveButtonMethod "customTagStart" o = Gtk.Buildable.BuildableCustomTagStartMethodInfo
    ResolveButtonMethod "destroy" o = Gtk.Widget.WidgetDestroyMethodInfo
    ResolveButtonMethod "destroyed" o = Gtk.Widget.WidgetDestroyedMethodInfo
    ResolveButtonMethod "deviceIsShadowed" o = Gtk.Widget.WidgetDeviceIsShadowedMethodInfo
    ResolveButtonMethod "doSetRelatedAction" o = Gtk.Activatable.ActivatableDoSetRelatedActionMethodInfo
    ResolveButtonMethod "dragBegin" o = Gtk.Widget.WidgetDragBeginMethodInfo
    ResolveButtonMethod "dragBeginWithCoordinates" o = Gtk.Widget.WidgetDragBeginWithCoordinatesMethodInfo
    ResolveButtonMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
    ResolveButtonMethod "dragDestAddImageTargets" o = Gtk.Widget.WidgetDragDestAddImageTargetsMethodInfo
    ResolveButtonMethod "dragDestAddTextTargets" o = Gtk.Widget.WidgetDragDestAddTextTargetsMethodInfo
    ResolveButtonMethod "dragDestAddUriTargets" o = Gtk.Widget.WidgetDragDestAddUriTargetsMethodInfo
    ResolveButtonMethod "dragDestFindTarget" o = Gtk.Widget.WidgetDragDestFindTargetMethodInfo
    ResolveButtonMethod "dragDestGetTargetList" o = Gtk.Widget.WidgetDragDestGetTargetListMethodInfo
    ResolveButtonMethod "dragDestGetTrackMotion" o = Gtk.Widget.WidgetDragDestGetTrackMotionMethodInfo
    ResolveButtonMethod "dragDestSet" o = Gtk.Widget.WidgetDragDestSetMethodInfo
    ResolveButtonMethod "dragDestSetProxy" o = Gtk.Widget.WidgetDragDestSetProxyMethodInfo
    ResolveButtonMethod "dragDestSetTargetList" o = Gtk.Widget.WidgetDragDestSetTargetListMethodInfo
    ResolveButtonMethod "dragDestSetTrackMotion" o = Gtk.Widget.WidgetDragDestSetTrackMotionMethodInfo
    ResolveButtonMethod "dragDestUnset" o = Gtk.Widget.WidgetDragDestUnsetMethodInfo
    ResolveButtonMethod "dragGetData" o = Gtk.Widget.WidgetDragGetDataMethodInfo
    ResolveButtonMethod "dragHighlight" o = Gtk.Widget.WidgetDragHighlightMethodInfo
    ResolveButtonMethod "dragSourceAddImageTargets" o = Gtk.Widget.WidgetDragSourceAddImageTargetsMethodInfo
    ResolveButtonMethod "dragSourceAddTextTargets" o = Gtk.Widget.WidgetDragSourceAddTextTargetsMethodInfo
    ResolveButtonMethod "dragSourceAddUriTargets" o = Gtk.Widget.WidgetDragSourceAddUriTargetsMethodInfo
    ResolveButtonMethod "dragSourceGetTargetList" o = Gtk.Widget.WidgetDragSourceGetTargetListMethodInfo
    ResolveButtonMethod "dragSourceSet" o = Gtk.Widget.WidgetDragSourceSetMethodInfo
    ResolveButtonMethod "dragSourceSetIconGicon" o = Gtk.Widget.WidgetDragSourceSetIconGiconMethodInfo
    ResolveButtonMethod "dragSourceSetIconName" o = Gtk.Widget.WidgetDragSourceSetIconNameMethodInfo
    ResolveButtonMethod "dragSourceSetIconPixbuf" o = Gtk.Widget.WidgetDragSourceSetIconPixbufMethodInfo
    ResolveButtonMethod "dragSourceSetIconStock" o = Gtk.Widget.WidgetDragSourceSetIconStockMethodInfo
    ResolveButtonMethod "dragSourceSetTargetList" o = Gtk.Widget.WidgetDragSourceSetTargetListMethodInfo
    ResolveButtonMethod "dragSourceUnset" o = Gtk.Widget.WidgetDragSourceUnsetMethodInfo
    ResolveButtonMethod "dragUnhighlight" o = Gtk.Widget.WidgetDragUnhighlightMethodInfo
    ResolveButtonMethod "draw" o = Gtk.Widget.WidgetDrawMethodInfo
    ResolveButtonMethod "ensureStyle" o = Gtk.Widget.WidgetEnsureStyleMethodInfo
    ResolveButtonMethod "enter" o = ButtonEnterMethodInfo
    ResolveButtonMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
    ResolveButtonMethod "event" o = Gtk.Widget.WidgetEventMethodInfo
    ResolveButtonMethod "forall" o = Gtk.Container.ContainerForallMethodInfo
    ResolveButtonMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveButtonMethod "foreach" o = Gtk.Container.ContainerForeachMethodInfo
    ResolveButtonMethod "freezeChildNotify" o = Gtk.Widget.WidgetFreezeChildNotifyMethodInfo
    ResolveButtonMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveButtonMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveButtonMethod "grabAdd" o = Gtk.Widget.WidgetGrabAddMethodInfo
    ResolveButtonMethod "grabDefault" o = Gtk.Widget.WidgetGrabDefaultMethodInfo
    ResolveButtonMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
    ResolveButtonMethod "grabRemove" o = Gtk.Widget.WidgetGrabRemoveMethodInfo
    ResolveButtonMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
    ResolveButtonMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
    ResolveButtonMethod "hasGrab" o = Gtk.Widget.WidgetHasGrabMethodInfo
    ResolveButtonMethod "hasRcStyle" o = Gtk.Widget.WidgetHasRcStyleMethodInfo
    ResolveButtonMethod "hasScreen" o = Gtk.Widget.WidgetHasScreenMethodInfo
    ResolveButtonMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
    ResolveButtonMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
    ResolveButtonMethod "hideOnDelete" o = Gtk.Widget.WidgetHideOnDeleteMethodInfo
    ResolveButtonMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
    ResolveButtonMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
    ResolveButtonMethod "inputShapeCombineRegion" o = Gtk.Widget.WidgetInputShapeCombineRegionMethodInfo
    ResolveButtonMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
    ResolveButtonMethod "intersect" o = Gtk.Widget.WidgetIntersectMethodInfo
    ResolveButtonMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
    ResolveButtonMethod "isComposited" o = Gtk.Widget.WidgetIsCompositedMethodInfo
    ResolveButtonMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
    ResolveButtonMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveButtonMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
    ResolveButtonMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
    ResolveButtonMethod "isToplevel" o = Gtk.Widget.WidgetIsToplevelMethodInfo
    ResolveButtonMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
    ResolveButtonMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
    ResolveButtonMethod "leave" o = ButtonLeaveMethodInfo
    ResolveButtonMethod "listAccelClosures" o = Gtk.Widget.WidgetListAccelClosuresMethodInfo
    ResolveButtonMethod "listActionPrefixes" o = Gtk.Widget.WidgetListActionPrefixesMethodInfo
    ResolveButtonMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
    ResolveButtonMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
    ResolveButtonMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
    ResolveButtonMethod "modifyBase" o = Gtk.Widget.WidgetModifyBaseMethodInfo
    ResolveButtonMethod "modifyBg" o = Gtk.Widget.WidgetModifyBgMethodInfo
    ResolveButtonMethod "modifyCursor" o = Gtk.Widget.WidgetModifyCursorMethodInfo
    ResolveButtonMethod "modifyFg" o = Gtk.Widget.WidgetModifyFgMethodInfo
    ResolveButtonMethod "modifyFont" o = Gtk.Widget.WidgetModifyFontMethodInfo
    ResolveButtonMethod "modifyStyle" o = Gtk.Widget.WidgetModifyStyleMethodInfo
    ResolveButtonMethod "modifyText" o = Gtk.Widget.WidgetModifyTextMethodInfo
    ResolveButtonMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveButtonMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveButtonMethod "overrideBackgroundColor" o = Gtk.Widget.WidgetOverrideBackgroundColorMethodInfo
    ResolveButtonMethod "overrideColor" o = Gtk.Widget.WidgetOverrideColorMethodInfo
    ResolveButtonMethod "overrideCursor" o = Gtk.Widget.WidgetOverrideCursorMethodInfo
    ResolveButtonMethod "overrideFont" o = Gtk.Widget.WidgetOverrideFontMethodInfo
    ResolveButtonMethod "overrideSymbolicColor" o = Gtk.Widget.WidgetOverrideSymbolicColorMethodInfo
    ResolveButtonMethod "parserFinished" o = Gtk.Buildable.BuildableParserFinishedMethodInfo
    ResolveButtonMethod "path" o = Gtk.Widget.WidgetPathMethodInfo
    ResolveButtonMethod "pressed" o = ButtonPressedMethodInfo
    ResolveButtonMethod "propagateDraw" o = Gtk.Container.ContainerPropagateDrawMethodInfo
    ResolveButtonMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
    ResolveButtonMethod "queueComputeExpand" o = Gtk.Widget.WidgetQueueComputeExpandMethodInfo
    ResolveButtonMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
    ResolveButtonMethod "queueDrawArea" o = Gtk.Widget.WidgetQueueDrawAreaMethodInfo
    ResolveButtonMethod "queueDrawRegion" o = Gtk.Widget.WidgetQueueDrawRegionMethodInfo
    ResolveButtonMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
    ResolveButtonMethod "queueResizeNoRedraw" o = Gtk.Widget.WidgetQueueResizeNoRedrawMethodInfo
    ResolveButtonMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
    ResolveButtonMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveButtonMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveButtonMethod "regionIntersect" o = Gtk.Widget.WidgetRegionIntersectMethodInfo
    ResolveButtonMethod "registerWindow" o = Gtk.Widget.WidgetRegisterWindowMethodInfo
    ResolveButtonMethod "released" o = ButtonReleasedMethodInfo
    ResolveButtonMethod "remove" o = Gtk.Container.ContainerRemoveMethodInfo
    ResolveButtonMethod "removeAccelerator" o = Gtk.Widget.WidgetRemoveAcceleratorMethodInfo
    ResolveButtonMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
    ResolveButtonMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
    ResolveButtonMethod "renderIcon" o = Gtk.Widget.WidgetRenderIconMethodInfo
    ResolveButtonMethod "renderIconPixbuf" o = Gtk.Widget.WidgetRenderIconPixbufMethodInfo
    ResolveButtonMethod "reparent" o = Gtk.Widget.WidgetReparentMethodInfo
    ResolveButtonMethod "resetRcStyles" o = Gtk.Widget.WidgetResetRcStylesMethodInfo
    ResolveButtonMethod "resetStyle" o = Gtk.Widget.WidgetResetStyleMethodInfo
    ResolveButtonMethod "resizeChildren" o = Gtk.Container.ContainerResizeChildrenMethodInfo
    ResolveButtonMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveButtonMethod "sendExpose" o = Gtk.Widget.WidgetSendExposeMethodInfo
    ResolveButtonMethod "sendFocusChange" o = Gtk.Widget.WidgetSendFocusChangeMethodInfo
    ResolveButtonMethod "shapeCombineRegion" o = Gtk.Widget.WidgetShapeCombineRegionMethodInfo
    ResolveButtonMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
    ResolveButtonMethod "showAll" o = Gtk.Widget.WidgetShowAllMethodInfo
    ResolveButtonMethod "showNow" o = Gtk.Widget.WidgetShowNowMethodInfo
    ResolveButtonMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
    ResolveButtonMethod "sizeAllocateWithBaseline" o = Gtk.Widget.WidgetSizeAllocateWithBaselineMethodInfo
    ResolveButtonMethod "sizeRequest" o = Gtk.Widget.WidgetSizeRequestMethodInfo
    ResolveButtonMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveButtonMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveButtonMethod "styleAttach" o = Gtk.Widget.WidgetStyleAttachMethodInfo
    ResolveButtonMethod "styleGetProperty" o = Gtk.Widget.WidgetStyleGetPropertyMethodInfo
    ResolveButtonMethod "syncActionProperties" o = Gtk.Activatable.ActivatableSyncActionPropertiesMethodInfo
    ResolveButtonMethod "thawChildNotify" o = Gtk.Widget.WidgetThawChildNotifyMethodInfo
    ResolveButtonMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveButtonMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
    ResolveButtonMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
    ResolveButtonMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
    ResolveButtonMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
    ResolveButtonMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
    ResolveButtonMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveButtonMethod "unregisterWindow" o = Gtk.Widget.WidgetUnregisterWindowMethodInfo
    ResolveButtonMethod "unsetFocusChain" o = Gtk.Container.ContainerUnsetFocusChainMethodInfo
    ResolveButtonMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
    ResolveButtonMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveButtonMethod "getAccessible" o = Gtk.Widget.WidgetGetAccessibleMethodInfo
    ResolveButtonMethod "getActionGroup" o = Gtk.Widget.WidgetGetActionGroupMethodInfo
    ResolveButtonMethod "getActionName" o = Gtk.Actionable.ActionableGetActionNameMethodInfo
    ResolveButtonMethod "getActionTargetValue" o = Gtk.Actionable.ActionableGetActionTargetValueMethodInfo
    ResolveButtonMethod "getAlignment" o = ButtonGetAlignmentMethodInfo
    ResolveButtonMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
    ResolveButtonMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
    ResolveButtonMethod "getAllocatedSize" o = Gtk.Widget.WidgetGetAllocatedSizeMethodInfo
    ResolveButtonMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
    ResolveButtonMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
    ResolveButtonMethod "getAlwaysShowImage" o = ButtonGetAlwaysShowImageMethodInfo
    ResolveButtonMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
    ResolveButtonMethod "getAppPaintable" o = Gtk.Widget.WidgetGetAppPaintableMethodInfo
    ResolveButtonMethod "getBorderWidth" o = Gtk.Container.ContainerGetBorderWidthMethodInfo
    ResolveButtonMethod "getCanDefault" o = Gtk.Widget.WidgetGetCanDefaultMethodInfo
    ResolveButtonMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
    ResolveButtonMethod "getChild" o = Gtk.Bin.BinGetChildMethodInfo
    ResolveButtonMethod "getChildRequisition" o = Gtk.Widget.WidgetGetChildRequisitionMethodInfo
    ResolveButtonMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
    ResolveButtonMethod "getChildren" o = Gtk.Container.ContainerGetChildrenMethodInfo
    ResolveButtonMethod "getClip" o = Gtk.Widget.WidgetGetClipMethodInfo
    ResolveButtonMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
    ResolveButtonMethod "getCompositeName" o = Gtk.Widget.WidgetGetCompositeNameMethodInfo
    ResolveButtonMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveButtonMethod "getDeviceEnabled" o = Gtk.Widget.WidgetGetDeviceEnabledMethodInfo
    ResolveButtonMethod "getDeviceEvents" o = Gtk.Widget.WidgetGetDeviceEventsMethodInfo
    ResolveButtonMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
    ResolveButtonMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
    ResolveButtonMethod "getDoubleBuffered" o = Gtk.Widget.WidgetGetDoubleBufferedMethodInfo
    ResolveButtonMethod "getEventWindow" o = ButtonGetEventWindowMethodInfo
    ResolveButtonMethod "getEvents" o = Gtk.Widget.WidgetGetEventsMethodInfo
    ResolveButtonMethod "getFocusChain" o = Gtk.Container.ContainerGetFocusChainMethodInfo
    ResolveButtonMethod "getFocusChild" o = Gtk.Container.ContainerGetFocusChildMethodInfo
    ResolveButtonMethod "getFocusHadjustment" o = Gtk.Container.ContainerGetFocusHadjustmentMethodInfo
    ResolveButtonMethod "getFocusOnClick" o = ButtonGetFocusOnClickMethodInfo
    ResolveButtonMethod "getFocusVadjustment" o = Gtk.Container.ContainerGetFocusVadjustmentMethodInfo
    ResolveButtonMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
    ResolveButtonMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
    ResolveButtonMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
    ResolveButtonMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
    ResolveButtonMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
    ResolveButtonMethod "getHasWindow" o = Gtk.Widget.WidgetGetHasWindowMethodInfo
    ResolveButtonMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
    ResolveButtonMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
    ResolveButtonMethod "getImage" o = ButtonGetImageMethodInfo
    ResolveButtonMethod "getImagePosition" o = ButtonGetImagePositionMethodInfo
    ResolveButtonMethod "getInternalChild" o = Gtk.Buildable.BuildableGetInternalChildMethodInfo
    ResolveButtonMethod "getLabel" o = ButtonGetLabelMethodInfo
    ResolveButtonMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
    ResolveButtonMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
    ResolveButtonMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
    ResolveButtonMethod "getMarginLeft" o = Gtk.Widget.WidgetGetMarginLeftMethodInfo
    ResolveButtonMethod "getMarginRight" o = Gtk.Widget.WidgetGetMarginRightMethodInfo
    ResolveButtonMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
    ResolveButtonMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
    ResolveButtonMethod "getModifierMask" o = Gtk.Widget.WidgetGetModifierMaskMethodInfo
    ResolveButtonMethod "getModifierStyle" o = Gtk.Widget.WidgetGetModifierStyleMethodInfo
    ResolveButtonMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
    ResolveButtonMethod "getNoShowAll" o = Gtk.Widget.WidgetGetNoShowAllMethodInfo
    ResolveButtonMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
    ResolveButtonMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
    ResolveButtonMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
    ResolveButtonMethod "getParentWindow" o = Gtk.Widget.WidgetGetParentWindowMethodInfo
    ResolveButtonMethod "getPath" o = Gtk.Widget.WidgetGetPathMethodInfo
    ResolveButtonMethod "getPathForChild" o = Gtk.Container.ContainerGetPathForChildMethodInfo
    ResolveButtonMethod "getPointer" o = Gtk.Widget.WidgetGetPointerMethodInfo
    ResolveButtonMethod "getPreferredHeight" o = Gtk.Widget.WidgetGetPreferredHeightMethodInfo
    ResolveButtonMethod "getPreferredHeightAndBaselineForWidth" o = Gtk.Widget.WidgetGetPreferredHeightAndBaselineForWidthMethodInfo
    ResolveButtonMethod "getPreferredHeightForWidth" o = Gtk.Widget.WidgetGetPreferredHeightForWidthMethodInfo
    ResolveButtonMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
    ResolveButtonMethod "getPreferredWidth" o = Gtk.Widget.WidgetGetPreferredWidthMethodInfo
    ResolveButtonMethod "getPreferredWidthForHeight" o = Gtk.Widget.WidgetGetPreferredWidthForHeightMethodInfo
    ResolveButtonMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveButtonMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveButtonMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
    ResolveButtonMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
    ResolveButtonMethod "getRelatedAction" o = Gtk.Activatable.ActivatableGetRelatedActionMethodInfo
    ResolveButtonMethod "getRelief" o = ButtonGetReliefMethodInfo
    ResolveButtonMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
    ResolveButtonMethod "getRequisition" o = Gtk.Widget.WidgetGetRequisitionMethodInfo
    ResolveButtonMethod "getResizeMode" o = Gtk.Container.ContainerGetResizeModeMethodInfo
    ResolveButtonMethod "getRootWindow" o = Gtk.Widget.WidgetGetRootWindowMethodInfo
    ResolveButtonMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
    ResolveButtonMethod "getScreen" o = Gtk.Widget.WidgetGetScreenMethodInfo
    ResolveButtonMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
    ResolveButtonMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
    ResolveButtonMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
    ResolveButtonMethod "getState" o = Gtk.Widget.WidgetGetStateMethodInfo
    ResolveButtonMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
    ResolveButtonMethod "getStyle" o = Gtk.Widget.WidgetGetStyleMethodInfo
    ResolveButtonMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
    ResolveButtonMethod "getSupportMultidevice" o = Gtk.Widget.WidgetGetSupportMultideviceMethodInfo
    ResolveButtonMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
    ResolveButtonMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
    ResolveButtonMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
    ResolveButtonMethod "getTooltipWindow" o = Gtk.Widget.WidgetGetTooltipWindowMethodInfo
    ResolveButtonMethod "getToplevel" o = Gtk.Widget.WidgetGetToplevelMethodInfo
    ResolveButtonMethod "getUseActionAppearance" o = Gtk.Activatable.ActivatableGetUseActionAppearanceMethodInfo
    ResolveButtonMethod "getUseStock" o = ButtonGetUseStockMethodInfo
    ResolveButtonMethod "getUseUnderline" o = ButtonGetUseUnderlineMethodInfo
    ResolveButtonMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
    ResolveButtonMethod "getValignWithBaseline" o = Gtk.Widget.WidgetGetValignWithBaselineMethodInfo
    ResolveButtonMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
    ResolveButtonMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
    ResolveButtonMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
    ResolveButtonMethod "getVisual" o = Gtk.Widget.WidgetGetVisualMethodInfo
    ResolveButtonMethod "getWindow" o = Gtk.Widget.WidgetGetWindowMethodInfo
    ResolveButtonMethod "setAccelPath" o = Gtk.Widget.WidgetSetAccelPathMethodInfo
    ResolveButtonMethod "setActionName" o = Gtk.Actionable.ActionableSetActionNameMethodInfo
    ResolveButtonMethod "setActionTargetValue" o = Gtk.Actionable.ActionableSetActionTargetValueMethodInfo
    ResolveButtonMethod "setAlignment" o = ButtonSetAlignmentMethodInfo
    ResolveButtonMethod "setAllocation" o = Gtk.Widget.WidgetSetAllocationMethodInfo
    ResolveButtonMethod "setAlwaysShowImage" o = ButtonSetAlwaysShowImageMethodInfo
    ResolveButtonMethod "setAppPaintable" o = Gtk.Widget.WidgetSetAppPaintableMethodInfo
    ResolveButtonMethod "setBorderWidth" o = Gtk.Container.ContainerSetBorderWidthMethodInfo
    ResolveButtonMethod "setBuildableProperty" o = Gtk.Buildable.BuildableSetBuildablePropertyMethodInfo
    ResolveButtonMethod "setCanDefault" o = Gtk.Widget.WidgetSetCanDefaultMethodInfo
    ResolveButtonMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
    ResolveButtonMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
    ResolveButtonMethod "setClip" o = Gtk.Widget.WidgetSetClipMethodInfo
    ResolveButtonMethod "setCompositeName" o = Gtk.Widget.WidgetSetCompositeNameMethodInfo
    ResolveButtonMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveButtonMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveButtonMethod "setDetailedActionName" o = Gtk.Actionable.ActionableSetDetailedActionNameMethodInfo
    ResolveButtonMethod "setDeviceEnabled" o = Gtk.Widget.WidgetSetDeviceEnabledMethodInfo
    ResolveButtonMethod "setDeviceEvents" o = Gtk.Widget.WidgetSetDeviceEventsMethodInfo
    ResolveButtonMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
    ResolveButtonMethod "setDoubleBuffered" o = Gtk.Widget.WidgetSetDoubleBufferedMethodInfo
    ResolveButtonMethod "setEvents" o = Gtk.Widget.WidgetSetEventsMethodInfo
    ResolveButtonMethod "setFocusChain" o = Gtk.Container.ContainerSetFocusChainMethodInfo
    ResolveButtonMethod "setFocusChild" o = Gtk.Container.ContainerSetFocusChildMethodInfo
    ResolveButtonMethod "setFocusHadjustment" o = Gtk.Container.ContainerSetFocusHadjustmentMethodInfo
    ResolveButtonMethod "setFocusOnClick" o = ButtonSetFocusOnClickMethodInfo
    ResolveButtonMethod "setFocusVadjustment" o = Gtk.Container.ContainerSetFocusVadjustmentMethodInfo
    ResolveButtonMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
    ResolveButtonMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
    ResolveButtonMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
    ResolveButtonMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
    ResolveButtonMethod "setHasWindow" o = Gtk.Widget.WidgetSetHasWindowMethodInfo
    ResolveButtonMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
    ResolveButtonMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
    ResolveButtonMethod "setImage" o = ButtonSetImageMethodInfo
    ResolveButtonMethod "setImagePosition" o = ButtonSetImagePositionMethodInfo
    ResolveButtonMethod "setLabel" o = ButtonSetLabelMethodInfo
    ResolveButtonMethod "setMapped" o = Gtk.Widget.WidgetSetMappedMethodInfo
    ResolveButtonMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
    ResolveButtonMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
    ResolveButtonMethod "setMarginLeft" o = Gtk.Widget.WidgetSetMarginLeftMethodInfo
    ResolveButtonMethod "setMarginRight" o = Gtk.Widget.WidgetSetMarginRightMethodInfo
    ResolveButtonMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
    ResolveButtonMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
    ResolveButtonMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
    ResolveButtonMethod "setNoShowAll" o = Gtk.Widget.WidgetSetNoShowAllMethodInfo
    ResolveButtonMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
    ResolveButtonMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
    ResolveButtonMethod "setParentWindow" o = Gtk.Widget.WidgetSetParentWindowMethodInfo
    ResolveButtonMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveButtonMethod "setRealized" o = Gtk.Widget.WidgetSetRealizedMethodInfo
    ResolveButtonMethod "setReallocateRedraws" o = Gtk.Container.ContainerSetReallocateRedrawsMethodInfo
    ResolveButtonMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
    ResolveButtonMethod "setRedrawOnAllocate" o = Gtk.Widget.WidgetSetRedrawOnAllocateMethodInfo
    ResolveButtonMethod "setRelatedAction" o = Gtk.Activatable.ActivatableSetRelatedActionMethodInfo
    ResolveButtonMethod "setRelief" o = ButtonSetReliefMethodInfo
    ResolveButtonMethod "setResizeMode" o = Gtk.Container.ContainerSetResizeModeMethodInfo
    ResolveButtonMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
    ResolveButtonMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
    ResolveButtonMethod "setState" o = Gtk.Widget.WidgetSetStateMethodInfo
    ResolveButtonMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
    ResolveButtonMethod "setStyle" o = Gtk.Widget.WidgetSetStyleMethodInfo
    ResolveButtonMethod "setSupportMultidevice" o = Gtk.Widget.WidgetSetSupportMultideviceMethodInfo
    ResolveButtonMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
    ResolveButtonMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
    ResolveButtonMethod "setTooltipWindow" o = Gtk.Widget.WidgetSetTooltipWindowMethodInfo
    ResolveButtonMethod "setUseActionAppearance" o = Gtk.Activatable.ActivatableSetUseActionAppearanceMethodInfo
    ResolveButtonMethod "setUseStock" o = ButtonSetUseStockMethodInfo
    ResolveButtonMethod "setUseUnderline" o = ButtonSetUseUnderlineMethodInfo
    ResolveButtonMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
    ResolveButtonMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
    ResolveButtonMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
    ResolveButtonMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
    ResolveButtonMethod "setVisual" o = Gtk.Widget.WidgetSetVisualMethodInfo
    ResolveButtonMethod "setWindow" o = Gtk.Widget.WidgetSetWindowMethodInfo
    ResolveButtonMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveButtonMethod t Button, O.OverloadedMethod info Button p) => OL.IsLabel t (Button -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif
#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveButtonMethod t Button, O.OverloadedMethod info Button p, R.HasField t Button p) => R.HasField t Button p where
    getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveButtonMethod t Button, O.OverloadedMethodInfo info Button) => OL.IsLabel t (O.MethodProxy info Button) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif
#endif
type ButtonActivateCallback =
    IO ()
noButtonActivateCallback :: Maybe ButtonActivateCallback
noButtonActivateCallback :: Maybe (IO ())
noButtonActivateCallback = Maybe (IO ())
forall a. Maybe a
Nothing
type C_ButtonActivateCallback =
    Ptr () ->                               
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_ButtonActivateCallback :: C_ButtonActivateCallback -> IO (FunPtr C_ButtonActivateCallback)
genClosure_ButtonActivate :: MonadIO m => ButtonActivateCallback -> m (GClosure C_ButtonActivateCallback)
genClosure_ButtonActivate :: forall (m :: * -> *).
MonadIO m =>
IO () -> m (GClosure C_ButtonActivateCallback)
genClosure_ButtonActivate IO ()
cb = IO (GClosure C_ButtonActivateCallback)
-> m (GClosure C_ButtonActivateCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_ButtonActivateCallback)
 -> m (GClosure C_ButtonActivateCallback))
-> IO (GClosure C_ButtonActivateCallback)
-> m (GClosure C_ButtonActivateCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ButtonActivateCallback
cb' = IO () -> C_ButtonActivateCallback
wrap_ButtonActivateCallback IO ()
cb
    C_ButtonActivateCallback -> IO (FunPtr C_ButtonActivateCallback)
mk_ButtonActivateCallback C_ButtonActivateCallback
cb' IO (FunPtr C_ButtonActivateCallback)
-> (FunPtr C_ButtonActivateCallback
    -> IO (GClosure C_ButtonActivateCallback))
-> IO (GClosure C_ButtonActivateCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_ButtonActivateCallback
-> IO (GClosure C_ButtonActivateCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_ButtonActivateCallback ::
    ButtonActivateCallback ->
    C_ButtonActivateCallback
wrap_ButtonActivateCallback :: IO () -> C_ButtonActivateCallback
wrap_ButtonActivateCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
    IO ()
_cb 
onButtonActivate :: (IsButton a, MonadIO m) => a -> ButtonActivateCallback -> m SignalHandlerId
onButtonActivate :: forall a (m :: * -> *).
(IsButton a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
onButtonActivate a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ButtonActivateCallback
cb' = IO () -> C_ButtonActivateCallback
wrap_ButtonActivateCallback IO ()
cb
    FunPtr C_ButtonActivateCallback
cb'' <- C_ButtonActivateCallback -> IO (FunPtr C_ButtonActivateCallback)
mk_ButtonActivateCallback C_ButtonActivateCallback
cb'
    a
-> Text
-> FunPtr C_ButtonActivateCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"activate" FunPtr C_ButtonActivateCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterButtonActivate :: (IsButton a, MonadIO m) => a -> ButtonActivateCallback -> m SignalHandlerId
afterButtonActivate :: forall a (m :: * -> *).
(IsButton a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
afterButtonActivate a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ButtonActivateCallback
cb' = IO () -> C_ButtonActivateCallback
wrap_ButtonActivateCallback IO ()
cb
    FunPtr C_ButtonActivateCallback
cb'' <- C_ButtonActivateCallback -> IO (FunPtr C_ButtonActivateCallback)
mk_ButtonActivateCallback C_ButtonActivateCallback
cb'
    a
-> Text
-> FunPtr C_ButtonActivateCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"activate" FunPtr C_ButtonActivateCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data ButtonActivateSignalInfo
instance SignalInfo ButtonActivateSignalInfo where
    type HaskellCallbackType ButtonActivateSignalInfo = ButtonActivateCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_ButtonActivateCallback cb
        cb'' <- mk_ButtonActivateCallback cb'
        connectSignalFunPtr obj "activate" cb'' connectMode detail
#endif
type ButtonClickedCallback =
    IO ()
noButtonClickedCallback :: Maybe ButtonClickedCallback
noButtonClickedCallback :: Maybe (IO ())
noButtonClickedCallback = Maybe (IO ())
forall a. Maybe a
Nothing
type C_ButtonClickedCallback =
    Ptr () ->                               
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_ButtonClickedCallback :: C_ButtonClickedCallback -> IO (FunPtr C_ButtonClickedCallback)
genClosure_ButtonClicked :: MonadIO m => ButtonClickedCallback -> m (GClosure C_ButtonClickedCallback)
genClosure_ButtonClicked :: forall (m :: * -> *).
MonadIO m =>
IO () -> m (GClosure C_ButtonActivateCallback)
genClosure_ButtonClicked IO ()
cb = IO (GClosure C_ButtonActivateCallback)
-> m (GClosure C_ButtonActivateCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_ButtonActivateCallback)
 -> m (GClosure C_ButtonActivateCallback))
-> IO (GClosure C_ButtonActivateCallback)
-> m (GClosure C_ButtonActivateCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ButtonActivateCallback
cb' = IO () -> C_ButtonActivateCallback
wrap_ButtonClickedCallback IO ()
cb
    C_ButtonActivateCallback -> IO (FunPtr C_ButtonActivateCallback)
mk_ButtonClickedCallback C_ButtonActivateCallback
cb' IO (FunPtr C_ButtonActivateCallback)
-> (FunPtr C_ButtonActivateCallback
    -> IO (GClosure C_ButtonActivateCallback))
-> IO (GClosure C_ButtonActivateCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_ButtonActivateCallback
-> IO (GClosure C_ButtonActivateCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_ButtonClickedCallback ::
    ButtonClickedCallback ->
    C_ButtonClickedCallback
wrap_ButtonClickedCallback :: IO () -> C_ButtonActivateCallback
wrap_ButtonClickedCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
    IO ()
_cb 
onButtonClicked :: (IsButton a, MonadIO m) => a -> ButtonClickedCallback -> m SignalHandlerId
onButtonClicked :: forall a (m :: * -> *).
(IsButton a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
onButtonClicked a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ButtonActivateCallback
cb' = IO () -> C_ButtonActivateCallback
wrap_ButtonClickedCallback IO ()
cb
    FunPtr C_ButtonActivateCallback
cb'' <- C_ButtonActivateCallback -> IO (FunPtr C_ButtonActivateCallback)
mk_ButtonClickedCallback C_ButtonActivateCallback
cb'
    a
-> Text
-> FunPtr C_ButtonActivateCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"clicked" FunPtr C_ButtonActivateCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterButtonClicked :: (IsButton a, MonadIO m) => a -> ButtonClickedCallback -> m SignalHandlerId
afterButtonClicked :: forall a (m :: * -> *).
(IsButton a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
afterButtonClicked a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ButtonActivateCallback
cb' = IO () -> C_ButtonActivateCallback
wrap_ButtonClickedCallback IO ()
cb
    FunPtr C_ButtonActivateCallback
cb'' <- C_ButtonActivateCallback -> IO (FunPtr C_ButtonActivateCallback)
mk_ButtonClickedCallback C_ButtonActivateCallback
cb'
    a
-> Text
-> FunPtr C_ButtonActivateCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"clicked" FunPtr C_ButtonActivateCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data ButtonClickedSignalInfo
instance SignalInfo ButtonClickedSignalInfo where
    type HaskellCallbackType ButtonClickedSignalInfo = ButtonClickedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_ButtonClickedCallback cb
        cb'' <- mk_ButtonClickedCallback cb'
        connectSignalFunPtr obj "clicked" cb'' connectMode detail
#endif
{-# DEPRECATED ButtonEnterCallback ["(Since version 2.8)","Use the [enterNotifyEvent](\"GI.Gtk.Objects.Widget#g:signal:enterNotifyEvent\") signal."] #-}
type ButtonEnterCallback =
    IO ()
noButtonEnterCallback :: Maybe ButtonEnterCallback
noButtonEnterCallback :: Maybe (IO ())
noButtonEnterCallback = Maybe (IO ())
forall a. Maybe a
Nothing
type C_ButtonEnterCallback =
    Ptr () ->                               
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_ButtonEnterCallback :: C_ButtonEnterCallback -> IO (FunPtr C_ButtonEnterCallback)
genClosure_ButtonEnter :: MonadIO m => ButtonEnterCallback -> m (GClosure C_ButtonEnterCallback)
genClosure_ButtonEnter :: forall (m :: * -> *).
MonadIO m =>
IO () -> m (GClosure C_ButtonActivateCallback)
genClosure_ButtonEnter IO ()
cb = IO (GClosure C_ButtonActivateCallback)
-> m (GClosure C_ButtonActivateCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_ButtonActivateCallback)
 -> m (GClosure C_ButtonActivateCallback))
-> IO (GClosure C_ButtonActivateCallback)
-> m (GClosure C_ButtonActivateCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ButtonActivateCallback
cb' = IO () -> C_ButtonActivateCallback
wrap_ButtonEnterCallback IO ()
cb
    C_ButtonActivateCallback -> IO (FunPtr C_ButtonActivateCallback)
mk_ButtonEnterCallback C_ButtonActivateCallback
cb' IO (FunPtr C_ButtonActivateCallback)
-> (FunPtr C_ButtonActivateCallback
    -> IO (GClosure C_ButtonActivateCallback))
-> IO (GClosure C_ButtonActivateCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_ButtonActivateCallback
-> IO (GClosure C_ButtonActivateCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_ButtonEnterCallback ::
    ButtonEnterCallback ->
    C_ButtonEnterCallback
wrap_ButtonEnterCallback :: IO () -> C_ButtonActivateCallback
wrap_ButtonEnterCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
    IO ()
_cb 
onButtonEnter :: (IsButton a, MonadIO m) => a -> ButtonEnterCallback -> m SignalHandlerId
onButtonEnter :: forall a (m :: * -> *).
(IsButton a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
onButtonEnter a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ButtonActivateCallback
cb' = IO () -> C_ButtonActivateCallback
wrap_ButtonEnterCallback IO ()
cb
    FunPtr C_ButtonActivateCallback
cb'' <- C_ButtonActivateCallback -> IO (FunPtr C_ButtonActivateCallback)
mk_ButtonEnterCallback C_ButtonActivateCallback
cb'
    a
-> Text
-> FunPtr C_ButtonActivateCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"enter" FunPtr C_ButtonActivateCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterButtonEnter :: (IsButton a, MonadIO m) => a -> ButtonEnterCallback -> m SignalHandlerId
afterButtonEnter :: forall a (m :: * -> *).
(IsButton a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
afterButtonEnter a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ButtonActivateCallback
cb' = IO () -> C_ButtonActivateCallback
wrap_ButtonEnterCallback IO ()
cb
    FunPtr C_ButtonActivateCallback
cb'' <- C_ButtonActivateCallback -> IO (FunPtr C_ButtonActivateCallback)
mk_ButtonEnterCallback C_ButtonActivateCallback
cb'
    a
-> Text
-> FunPtr C_ButtonActivateCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"enter" FunPtr C_ButtonActivateCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data ButtonEnterSignalInfo
instance SignalInfo ButtonEnterSignalInfo where
    type HaskellCallbackType ButtonEnterSignalInfo = ButtonEnterCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_ButtonEnterCallback cb
        cb'' <- mk_ButtonEnterCallback cb'
        connectSignalFunPtr obj "enter" cb'' connectMode detail
#endif
{-# DEPRECATED ButtonLeaveCallback ["(Since version 2.8)","Use the [leaveNotifyEvent](\"GI.Gtk.Objects.Widget#g:signal:leaveNotifyEvent\") signal."] #-}
type ButtonLeaveCallback =
    IO ()
noButtonLeaveCallback :: Maybe ButtonLeaveCallback
noButtonLeaveCallback :: Maybe (IO ())
noButtonLeaveCallback = Maybe (IO ())
forall a. Maybe a
Nothing
type C_ButtonLeaveCallback =
    Ptr () ->                               
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_ButtonLeaveCallback :: C_ButtonLeaveCallback -> IO (FunPtr C_ButtonLeaveCallback)
genClosure_ButtonLeave :: MonadIO m => ButtonLeaveCallback -> m (GClosure C_ButtonLeaveCallback)
genClosure_ButtonLeave :: forall (m :: * -> *).
MonadIO m =>
IO () -> m (GClosure C_ButtonActivateCallback)
genClosure_ButtonLeave IO ()
cb = IO (GClosure C_ButtonActivateCallback)
-> m (GClosure C_ButtonActivateCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_ButtonActivateCallback)
 -> m (GClosure C_ButtonActivateCallback))
-> IO (GClosure C_ButtonActivateCallback)
-> m (GClosure C_ButtonActivateCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ButtonActivateCallback
cb' = IO () -> C_ButtonActivateCallback
wrap_ButtonLeaveCallback IO ()
cb
    C_ButtonActivateCallback -> IO (FunPtr C_ButtonActivateCallback)
mk_ButtonLeaveCallback C_ButtonActivateCallback
cb' IO (FunPtr C_ButtonActivateCallback)
-> (FunPtr C_ButtonActivateCallback
    -> IO (GClosure C_ButtonActivateCallback))
-> IO (GClosure C_ButtonActivateCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_ButtonActivateCallback
-> IO (GClosure C_ButtonActivateCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_ButtonLeaveCallback ::
    ButtonLeaveCallback ->
    C_ButtonLeaveCallback
wrap_ButtonLeaveCallback :: IO () -> C_ButtonActivateCallback
wrap_ButtonLeaveCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
    IO ()
_cb 
onButtonLeave :: (IsButton a, MonadIO m) => a -> ButtonLeaveCallback -> m SignalHandlerId
onButtonLeave :: forall a (m :: * -> *).
(IsButton a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
onButtonLeave a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ButtonActivateCallback
cb' = IO () -> C_ButtonActivateCallback
wrap_ButtonLeaveCallback IO ()
cb
    FunPtr C_ButtonActivateCallback
cb'' <- C_ButtonActivateCallback -> IO (FunPtr C_ButtonActivateCallback)
mk_ButtonLeaveCallback C_ButtonActivateCallback
cb'
    a
-> Text
-> FunPtr C_ButtonActivateCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"leave" FunPtr C_ButtonActivateCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterButtonLeave :: (IsButton a, MonadIO m) => a -> ButtonLeaveCallback -> m SignalHandlerId
afterButtonLeave :: forall a (m :: * -> *).
(IsButton a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
afterButtonLeave a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ButtonActivateCallback
cb' = IO () -> C_ButtonActivateCallback
wrap_ButtonLeaveCallback IO ()
cb
    FunPtr C_ButtonActivateCallback
cb'' <- C_ButtonActivateCallback -> IO (FunPtr C_ButtonActivateCallback)
mk_ButtonLeaveCallback C_ButtonActivateCallback
cb'
    a
-> Text
-> FunPtr C_ButtonActivateCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"leave" FunPtr C_ButtonActivateCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data ButtonLeaveSignalInfo
instance SignalInfo ButtonLeaveSignalInfo where
    type HaskellCallbackType ButtonLeaveSignalInfo = ButtonLeaveCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_ButtonLeaveCallback cb
        cb'' <- mk_ButtonLeaveCallback cb'
        connectSignalFunPtr obj "leave" cb'' connectMode detail
#endif
{-# DEPRECATED ButtonPressedCallback ["(Since version 2.8)","Use the [buttonPressEvent](\"GI.Gtk.Objects.Widget#g:signal:buttonPressEvent\") signal."] #-}
type ButtonPressedCallback =
    IO ()
noButtonPressedCallback :: Maybe ButtonPressedCallback
noButtonPressedCallback :: Maybe (IO ())
noButtonPressedCallback = Maybe (IO ())
forall a. Maybe a
Nothing
type C_ButtonPressedCallback =
    Ptr () ->                               
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_ButtonPressedCallback :: C_ButtonPressedCallback -> IO (FunPtr C_ButtonPressedCallback)
genClosure_ButtonPressed :: MonadIO m => ButtonPressedCallback -> m (GClosure C_ButtonPressedCallback)
genClosure_ButtonPressed :: forall (m :: * -> *).
MonadIO m =>
IO () -> m (GClosure C_ButtonActivateCallback)
genClosure_ButtonPressed IO ()
cb = IO (GClosure C_ButtonActivateCallback)
-> m (GClosure C_ButtonActivateCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_ButtonActivateCallback)
 -> m (GClosure C_ButtonActivateCallback))
-> IO (GClosure C_ButtonActivateCallback)
-> m (GClosure C_ButtonActivateCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ButtonActivateCallback
cb' = IO () -> C_ButtonActivateCallback
wrap_ButtonPressedCallback IO ()
cb
    C_ButtonActivateCallback -> IO (FunPtr C_ButtonActivateCallback)
mk_ButtonPressedCallback C_ButtonActivateCallback
cb' IO (FunPtr C_ButtonActivateCallback)
-> (FunPtr C_ButtonActivateCallback
    -> IO (GClosure C_ButtonActivateCallback))
-> IO (GClosure C_ButtonActivateCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_ButtonActivateCallback
-> IO (GClosure C_ButtonActivateCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_ButtonPressedCallback ::
    ButtonPressedCallback ->
    C_ButtonPressedCallback
wrap_ButtonPressedCallback :: IO () -> C_ButtonActivateCallback
wrap_ButtonPressedCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
    IO ()
_cb 
onButtonPressed :: (IsButton a, MonadIO m) => a -> ButtonPressedCallback -> m SignalHandlerId
onButtonPressed :: forall a (m :: * -> *).
(IsButton a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
onButtonPressed a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ButtonActivateCallback
cb' = IO () -> C_ButtonActivateCallback
wrap_ButtonPressedCallback IO ()
cb
    FunPtr C_ButtonActivateCallback
cb'' <- C_ButtonActivateCallback -> IO (FunPtr C_ButtonActivateCallback)
mk_ButtonPressedCallback C_ButtonActivateCallback
cb'
    a
-> Text
-> FunPtr C_ButtonActivateCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"pressed" FunPtr C_ButtonActivateCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterButtonPressed :: (IsButton a, MonadIO m) => a -> ButtonPressedCallback -> m SignalHandlerId
afterButtonPressed :: forall a (m :: * -> *).
(IsButton a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
afterButtonPressed a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ButtonActivateCallback
cb' = IO () -> C_ButtonActivateCallback
wrap_ButtonPressedCallback IO ()
cb
    FunPtr C_ButtonActivateCallback
cb'' <- C_ButtonActivateCallback -> IO (FunPtr C_ButtonActivateCallback)
mk_ButtonPressedCallback C_ButtonActivateCallback
cb'
    a
-> Text
-> FunPtr C_ButtonActivateCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"pressed" FunPtr C_ButtonActivateCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data ButtonPressedSignalInfo
instance SignalInfo ButtonPressedSignalInfo where
    type HaskellCallbackType ButtonPressedSignalInfo = ButtonPressedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_ButtonPressedCallback cb
        cb'' <- mk_ButtonPressedCallback cb'
        connectSignalFunPtr obj "pressed" cb'' connectMode detail
#endif
{-# DEPRECATED ButtonReleasedCallback ["(Since version 2.8)","Use the [buttonReleaseEvent](\"GI.Gtk.Objects.Widget#g:signal:buttonReleaseEvent\") signal."] #-}
type ButtonReleasedCallback =
    IO ()
noButtonReleasedCallback :: Maybe ButtonReleasedCallback
noButtonReleasedCallback :: Maybe (IO ())
noButtonReleasedCallback = Maybe (IO ())
forall a. Maybe a
Nothing
type C_ButtonReleasedCallback =
    Ptr () ->                               
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_ButtonReleasedCallback :: C_ButtonReleasedCallback -> IO (FunPtr C_ButtonReleasedCallback)
genClosure_ButtonReleased :: MonadIO m => ButtonReleasedCallback -> m (GClosure C_ButtonReleasedCallback)
genClosure_ButtonReleased :: forall (m :: * -> *).
MonadIO m =>
IO () -> m (GClosure C_ButtonActivateCallback)
genClosure_ButtonReleased IO ()
cb = IO (GClosure C_ButtonActivateCallback)
-> m (GClosure C_ButtonActivateCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_ButtonActivateCallback)
 -> m (GClosure C_ButtonActivateCallback))
-> IO (GClosure C_ButtonActivateCallback)
-> m (GClosure C_ButtonActivateCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ButtonActivateCallback
cb' = IO () -> C_ButtonActivateCallback
wrap_ButtonReleasedCallback IO ()
cb
    C_ButtonActivateCallback -> IO (FunPtr C_ButtonActivateCallback)
mk_ButtonReleasedCallback C_ButtonActivateCallback
cb' IO (FunPtr C_ButtonActivateCallback)
-> (FunPtr C_ButtonActivateCallback
    -> IO (GClosure C_ButtonActivateCallback))
-> IO (GClosure C_ButtonActivateCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_ButtonActivateCallback
-> IO (GClosure C_ButtonActivateCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_ButtonReleasedCallback ::
    ButtonReleasedCallback ->
    C_ButtonReleasedCallback
wrap_ButtonReleasedCallback :: IO () -> C_ButtonActivateCallback
wrap_ButtonReleasedCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
    IO ()
_cb 
onButtonReleased :: (IsButton a, MonadIO m) => a -> ButtonReleasedCallback -> m SignalHandlerId
onButtonReleased :: forall a (m :: * -> *).
(IsButton a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
onButtonReleased a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ButtonActivateCallback
cb' = IO () -> C_ButtonActivateCallback
wrap_ButtonReleasedCallback IO ()
cb
    FunPtr C_ButtonActivateCallback
cb'' <- C_ButtonActivateCallback -> IO (FunPtr C_ButtonActivateCallback)
mk_ButtonReleasedCallback C_ButtonActivateCallback
cb'
    a
-> Text
-> FunPtr C_ButtonActivateCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"released" FunPtr C_ButtonActivateCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterButtonReleased :: (IsButton a, MonadIO m) => a -> ButtonReleasedCallback -> m SignalHandlerId
afterButtonReleased :: forall a (m :: * -> *).
(IsButton a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
afterButtonReleased a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ButtonActivateCallback
cb' = IO () -> C_ButtonActivateCallback
wrap_ButtonReleasedCallback IO ()
cb
    FunPtr C_ButtonActivateCallback
cb'' <- C_ButtonActivateCallback -> IO (FunPtr C_ButtonActivateCallback)
mk_ButtonReleasedCallback C_ButtonActivateCallback
cb'
    a
-> Text
-> FunPtr C_ButtonActivateCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"released" FunPtr C_ButtonActivateCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data ButtonReleasedSignalInfo
instance SignalInfo ButtonReleasedSignalInfo where
    type HaskellCallbackType ButtonReleasedSignalInfo = ButtonReleasedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_ButtonReleasedCallback cb
        cb'' <- mk_ButtonReleasedCallback cb'
        connectSignalFunPtr obj "released" cb'' connectMode detail
#endif
   
   
   
getButtonAlwaysShowImage :: (MonadIO m, IsButton o) => o -> m Bool
getButtonAlwaysShowImage :: forall (m :: * -> *) o. (MonadIO m, IsButton o) => o -> m Bool
getButtonAlwaysShowImage o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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 String
"always-show-image"
setButtonAlwaysShowImage :: (MonadIO m, IsButton o) => o -> Bool -> m ()
setButtonAlwaysShowImage :: forall (m :: * -> *) o.
(MonadIO m, IsButton o) =>
o -> Bool -> m ()
setButtonAlwaysShowImage o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"always-show-image" Bool
val
constructButtonAlwaysShowImage :: (IsButton o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructButtonAlwaysShowImage :: forall o (m :: * -> *).
(IsButton o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructButtonAlwaysShowImage Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"always-show-image" Bool
val
#if defined(ENABLE_OVERLOADING)
data ButtonAlwaysShowImagePropertyInfo
instance AttrInfo ButtonAlwaysShowImagePropertyInfo where
    type AttrAllowedOps ButtonAlwaysShowImagePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ButtonAlwaysShowImagePropertyInfo = IsButton
    type AttrSetTypeConstraint ButtonAlwaysShowImagePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint ButtonAlwaysShowImagePropertyInfo = (~) Bool
    type AttrTransferType ButtonAlwaysShowImagePropertyInfo = Bool
    type AttrGetType ButtonAlwaysShowImagePropertyInfo = Bool
    type AttrLabel ButtonAlwaysShowImagePropertyInfo = "always-show-image"
    type AttrOrigin ButtonAlwaysShowImagePropertyInfo = Button
    attrGet = getButtonAlwaysShowImage
    attrSet = setButtonAlwaysShowImage
    attrTransfer _ v = do
        return v
    attrConstruct = constructButtonAlwaysShowImage
    attrClear = undefined
#endif
   
   
   
getButtonImage :: (MonadIO m, IsButton o) => o -> m (Maybe Gtk.Widget.Widget)
getButtonImage :: forall (m :: * -> *) o.
(MonadIO m, IsButton o) =>
o -> m (Maybe Widget)
getButtonImage o
obj = IO (Maybe Widget) -> m (Maybe Widget)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Widget) -> m (Maybe Widget))
-> IO (Maybe Widget) -> m (Maybe Widget)
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr Widget -> Widget) -> IO (Maybe Widget)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"image" ManagedPtr Widget -> Widget
Gtk.Widget.Widget
setButtonImage :: (MonadIO m, IsButton o, Gtk.Widget.IsWidget a) => o -> a -> m ()
setButtonImage :: forall (m :: * -> *) o a.
(MonadIO m, IsButton o, IsWidget a) =>
o -> a -> m ()
setButtonImage o
obj a
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"image" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructButtonImage :: (IsButton o, MIO.MonadIO m, Gtk.Widget.IsWidget a) => a -> m (GValueConstruct o)
constructButtonImage :: forall o (m :: * -> *) a.
(IsButton o, MonadIO m, IsWidget a) =>
a -> m (GValueConstruct o)
constructButtonImage a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"image" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
clearButtonImage :: (MonadIO m, IsButton o) => o -> m ()
clearButtonImage :: forall (m :: * -> *) o. (MonadIO m, IsButton o) => o -> m ()
clearButtonImage 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 Widget -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"image" (Maybe Widget
forall a. Maybe a
Nothing :: Maybe Gtk.Widget.Widget)
#if defined(ENABLE_OVERLOADING)
data ButtonImagePropertyInfo
instance AttrInfo ButtonImagePropertyInfo where
    type AttrAllowedOps ButtonImagePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ButtonImagePropertyInfo = IsButton
    type AttrSetTypeConstraint ButtonImagePropertyInfo = Gtk.Widget.IsWidget
    type AttrTransferTypeConstraint ButtonImagePropertyInfo = Gtk.Widget.IsWidget
    type AttrTransferType ButtonImagePropertyInfo = Gtk.Widget.Widget
    type AttrGetType ButtonImagePropertyInfo = (Maybe Gtk.Widget.Widget)
    type AttrLabel ButtonImagePropertyInfo = "image"
    type AttrOrigin ButtonImagePropertyInfo = Button
    attrGet = getButtonImage
    attrSet = setButtonImage
    attrTransfer _ v = do
        unsafeCastTo Gtk.Widget.Widget v
    attrConstruct = constructButtonImage
    attrClear = clearButtonImage
#endif
   
   
   
getButtonImagePosition :: (MonadIO m, IsButton o) => o -> m Gtk.Enums.PositionType
getButtonImagePosition :: forall (m :: * -> *) o.
(MonadIO m, IsButton o) =>
o -> m PositionType
getButtonImagePosition o
obj = IO PositionType -> m PositionType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO PositionType -> m PositionType)
-> IO PositionType -> m PositionType
forall a b. (a -> b) -> a -> b
$ o -> String -> IO PositionType
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"image-position"
setButtonImagePosition :: (MonadIO m, IsButton o) => o -> Gtk.Enums.PositionType -> m ()
setButtonImagePosition :: forall (m :: * -> *) o.
(MonadIO m, IsButton o) =>
o -> PositionType -> m ()
setButtonImagePosition o
obj PositionType
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> PositionType -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj String
"image-position" PositionType
val
constructButtonImagePosition :: (IsButton o, MIO.MonadIO m) => Gtk.Enums.PositionType -> m (GValueConstruct o)
constructButtonImagePosition :: forall o (m :: * -> *).
(IsButton o, MonadIO m) =>
PositionType -> m (GValueConstruct o)
constructButtonImagePosition PositionType
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> PositionType -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"image-position" PositionType
val
#if defined(ENABLE_OVERLOADING)
data ButtonImagePositionPropertyInfo
instance AttrInfo ButtonImagePositionPropertyInfo where
    type AttrAllowedOps ButtonImagePositionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ButtonImagePositionPropertyInfo = IsButton
    type AttrSetTypeConstraint ButtonImagePositionPropertyInfo = (~) Gtk.Enums.PositionType
    type AttrTransferTypeConstraint ButtonImagePositionPropertyInfo = (~) Gtk.Enums.PositionType
    type AttrTransferType ButtonImagePositionPropertyInfo = Gtk.Enums.PositionType
    type AttrGetType ButtonImagePositionPropertyInfo = Gtk.Enums.PositionType
    type AttrLabel ButtonImagePositionPropertyInfo = "image-position"
    type AttrOrigin ButtonImagePositionPropertyInfo = Button
    attrGet = getButtonImagePosition
    attrSet = setButtonImagePosition
    attrTransfer _ v = do
        return v
    attrConstruct = constructButtonImagePosition
    attrClear = undefined
#endif
   
   
   
getButtonLabel :: (MonadIO m, IsButton o) => o -> m T.Text
getButtonLabel :: forall (m :: * -> *) o. (MonadIO m, IsButton o) => o -> m Text
getButtonLabel o
obj = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getButtonLabel" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"label"
setButtonLabel :: (MonadIO m, IsButton o) => o -> T.Text -> m ()
setButtonLabel :: forall (m :: * -> *) o.
(MonadIO m, IsButton o) =>
o -> Text -> m ()
setButtonLabel o
obj Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"label" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructButtonLabel :: (IsButton o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructButtonLabel :: forall o (m :: * -> *).
(IsButton o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructButtonLabel Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"label" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data ButtonLabelPropertyInfo
instance AttrInfo ButtonLabelPropertyInfo where
    type AttrAllowedOps ButtonLabelPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ButtonLabelPropertyInfo = IsButton
    type AttrSetTypeConstraint ButtonLabelPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint ButtonLabelPropertyInfo = (~) T.Text
    type AttrTransferType ButtonLabelPropertyInfo = T.Text
    type AttrGetType ButtonLabelPropertyInfo = T.Text
    type AttrLabel ButtonLabelPropertyInfo = "label"
    type AttrOrigin ButtonLabelPropertyInfo = Button
    attrGet = getButtonLabel
    attrSet = setButtonLabel
    attrTransfer _ v = do
        return v
    attrConstruct = constructButtonLabel
    attrClear = undefined
#endif
   
   
   
getButtonRelief :: (MonadIO m, IsButton o) => o -> m Gtk.Enums.ReliefStyle
getButtonRelief :: forall (m :: * -> *) o.
(MonadIO m, IsButton o) =>
o -> m ReliefStyle
getButtonRelief o
obj = IO ReliefStyle -> m ReliefStyle
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO ReliefStyle -> m ReliefStyle)
-> IO ReliefStyle -> m ReliefStyle
forall a b. (a -> b) -> a -> b
$ o -> String -> IO ReliefStyle
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"relief"
setButtonRelief :: (MonadIO m, IsButton o) => o -> Gtk.Enums.ReliefStyle -> m ()
setButtonRelief :: forall (m :: * -> *) o.
(MonadIO m, IsButton o) =>
o -> ReliefStyle -> m ()
setButtonRelief o
obj ReliefStyle
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> ReliefStyle -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj String
"relief" ReliefStyle
val
constructButtonRelief :: (IsButton o, MIO.MonadIO m) => Gtk.Enums.ReliefStyle -> m (GValueConstruct o)
constructButtonRelief :: forall o (m :: * -> *).
(IsButton o, MonadIO m) =>
ReliefStyle -> m (GValueConstruct o)
constructButtonRelief ReliefStyle
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> ReliefStyle -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"relief" ReliefStyle
val
#if defined(ENABLE_OVERLOADING)
data ButtonReliefPropertyInfo
instance AttrInfo ButtonReliefPropertyInfo where
    type AttrAllowedOps ButtonReliefPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ButtonReliefPropertyInfo = IsButton
    type AttrSetTypeConstraint ButtonReliefPropertyInfo = (~) Gtk.Enums.ReliefStyle
    type AttrTransferTypeConstraint ButtonReliefPropertyInfo = (~) Gtk.Enums.ReliefStyle
    type AttrTransferType ButtonReliefPropertyInfo = Gtk.Enums.ReliefStyle
    type AttrGetType ButtonReliefPropertyInfo = Gtk.Enums.ReliefStyle
    type AttrLabel ButtonReliefPropertyInfo = "relief"
    type AttrOrigin ButtonReliefPropertyInfo = Button
    attrGet = getButtonRelief
    attrSet = setButtonRelief
    attrTransfer _ v = do
        return v
    attrConstruct = constructButtonRelief
    attrClear = undefined
#endif
   
   
   
getButtonUseStock :: (MonadIO m, IsButton o) => o -> m Bool
getButtonUseStock :: forall (m :: * -> *) o. (MonadIO m, IsButton o) => o -> m Bool
getButtonUseStock o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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 String
"use-stock"
setButtonUseStock :: (MonadIO m, IsButton o) => o -> Bool -> m ()
setButtonUseStock :: forall (m :: * -> *) o.
(MonadIO m, IsButton o) =>
o -> Bool -> m ()
setButtonUseStock o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"use-stock" Bool
val
constructButtonUseStock :: (IsButton o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructButtonUseStock :: forall o (m :: * -> *).
(IsButton o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructButtonUseStock Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"use-stock" Bool
val
#if defined(ENABLE_OVERLOADING)
data ButtonUseStockPropertyInfo
instance AttrInfo ButtonUseStockPropertyInfo where
    type AttrAllowedOps ButtonUseStockPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ButtonUseStockPropertyInfo = IsButton
    type AttrSetTypeConstraint ButtonUseStockPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint ButtonUseStockPropertyInfo = (~) Bool
    type AttrTransferType ButtonUseStockPropertyInfo = Bool
    type AttrGetType ButtonUseStockPropertyInfo = Bool
    type AttrLabel ButtonUseStockPropertyInfo = "use-stock"
    type AttrOrigin ButtonUseStockPropertyInfo = Button
    attrGet = getButtonUseStock
    attrSet = setButtonUseStock
    attrTransfer _ v = do
        return v
    attrConstruct = constructButtonUseStock
    attrClear = undefined
#endif
   
   
   
getButtonUseUnderline :: (MonadIO m, IsButton o) => o -> m Bool
getButtonUseUnderline :: forall (m :: * -> *) o. (MonadIO m, IsButton o) => o -> m Bool
getButtonUseUnderline o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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 String
"use-underline"
setButtonUseUnderline :: (MonadIO m, IsButton o) => o -> Bool -> m ()
setButtonUseUnderline :: forall (m :: * -> *) o.
(MonadIO m, IsButton o) =>
o -> Bool -> m ()
setButtonUseUnderline o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"use-underline" Bool
val
constructButtonUseUnderline :: (IsButton o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructButtonUseUnderline :: forall o (m :: * -> *).
(IsButton o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructButtonUseUnderline Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"use-underline" Bool
val
#if defined(ENABLE_OVERLOADING)
data ButtonUseUnderlinePropertyInfo
instance AttrInfo ButtonUseUnderlinePropertyInfo where
    type AttrAllowedOps ButtonUseUnderlinePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ButtonUseUnderlinePropertyInfo = IsButton
    type AttrSetTypeConstraint ButtonUseUnderlinePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint ButtonUseUnderlinePropertyInfo = (~) Bool
    type AttrTransferType ButtonUseUnderlinePropertyInfo = Bool
    type AttrGetType ButtonUseUnderlinePropertyInfo = Bool
    type AttrLabel ButtonUseUnderlinePropertyInfo = "use-underline"
    type AttrOrigin ButtonUseUnderlinePropertyInfo = Button
    attrGet = getButtonUseUnderline
    attrSet = setButtonUseUnderline
    attrTransfer _ v = do
        return v
    attrConstruct = constructButtonUseUnderline
    attrClear = undefined
#endif
   
   
   
getButtonXalign :: (MonadIO m, IsButton o) => o -> m Float
getButtonXalign :: forall (m :: * -> *) o. (MonadIO m, IsButton o) => o -> m Float
getButtonXalign o
obj = IO Float -> m Float
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Float
forall a. GObject a => a -> String -> IO Float
B.Properties.getObjectPropertyFloat o
obj String
"xalign"
setButtonXalign :: (MonadIO m, IsButton o) => o -> Float -> m ()
setButtonXalign :: forall (m :: * -> *) o.
(MonadIO m, IsButton o) =>
o -> Float -> m ()
setButtonXalign o
obj Float
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Float -> IO ()
forall a. GObject a => a -> String -> Float -> IO ()
B.Properties.setObjectPropertyFloat o
obj String
"xalign" Float
val
constructButtonXalign :: (IsButton o, MIO.MonadIO m) => Float -> m (GValueConstruct o)
constructButtonXalign :: forall o (m :: * -> *).
(IsButton o, MonadIO m) =>
Float -> m (GValueConstruct o)
constructButtonXalign Float
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Float -> IO (GValueConstruct o)
forall o. String -> Float -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyFloat String
"xalign" Float
val
#if defined(ENABLE_OVERLOADING)
data ButtonXalignPropertyInfo
instance AttrInfo ButtonXalignPropertyInfo where
    type AttrAllowedOps ButtonXalignPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ButtonXalignPropertyInfo = IsButton
    type AttrSetTypeConstraint ButtonXalignPropertyInfo = (~) Float
    type AttrTransferTypeConstraint ButtonXalignPropertyInfo = (~) Float
    type AttrTransferType ButtonXalignPropertyInfo = Float
    type AttrGetType ButtonXalignPropertyInfo = Float
    type AttrLabel ButtonXalignPropertyInfo = "xalign"
    type AttrOrigin ButtonXalignPropertyInfo = Button
    attrGet = getButtonXalign
    attrSet = setButtonXalign
    attrTransfer _ v = do
        return v
    attrConstruct = constructButtonXalign
    attrClear = undefined
#endif
   
   
   
getButtonYalign :: (MonadIO m, IsButton o) => o -> m Float
getButtonYalign :: forall (m :: * -> *) o. (MonadIO m, IsButton o) => o -> m Float
getButtonYalign o
obj = IO Float -> m Float
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Float
forall a. GObject a => a -> String -> IO Float
B.Properties.getObjectPropertyFloat o
obj String
"yalign"
setButtonYalign :: (MonadIO m, IsButton o) => o -> Float -> m ()
setButtonYalign :: forall (m :: * -> *) o.
(MonadIO m, IsButton o) =>
o -> Float -> m ()
setButtonYalign o
obj Float
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Float -> IO ()
forall a. GObject a => a -> String -> Float -> IO ()
B.Properties.setObjectPropertyFloat o
obj String
"yalign" Float
val
constructButtonYalign :: (IsButton o, MIO.MonadIO m) => Float -> m (GValueConstruct o)
constructButtonYalign :: forall o (m :: * -> *).
(IsButton o, MonadIO m) =>
Float -> m (GValueConstruct o)
constructButtonYalign Float
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Float -> IO (GValueConstruct o)
forall o. String -> Float -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyFloat String
"yalign" Float
val
#if defined(ENABLE_OVERLOADING)
data ButtonYalignPropertyInfo
instance AttrInfo ButtonYalignPropertyInfo where
    type AttrAllowedOps ButtonYalignPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ButtonYalignPropertyInfo = IsButton
    type AttrSetTypeConstraint ButtonYalignPropertyInfo = (~) Float
    type AttrTransferTypeConstraint ButtonYalignPropertyInfo = (~) Float
    type AttrTransferType ButtonYalignPropertyInfo = Float
    type AttrGetType ButtonYalignPropertyInfo = Float
    type AttrLabel ButtonYalignPropertyInfo = "yalign"
    type AttrOrigin ButtonYalignPropertyInfo = Button
    attrGet = getButtonYalign
    attrSet = setButtonYalign
    attrTransfer _ v = do
        return v
    attrConstruct = constructButtonYalign
    attrClear = undefined
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Button
type instance O.AttributeList Button = ButtonAttributeList
type ButtonAttributeList = ('[ '("actionName", Gtk.Actionable.ActionableActionNamePropertyInfo), '("actionTarget", Gtk.Actionable.ActionableActionTargetPropertyInfo), '("alwaysShowImage", ButtonAlwaysShowImagePropertyInfo), '("appPaintable", Gtk.Widget.WidgetAppPaintablePropertyInfo), '("borderWidth", Gtk.Container.ContainerBorderWidthPropertyInfo), '("canDefault", Gtk.Widget.WidgetCanDefaultPropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("child", Gtk.Container.ContainerChildPropertyInfo), '("compositeChild", Gtk.Widget.WidgetCompositeChildPropertyInfo), '("doubleBuffered", Gtk.Widget.WidgetDoubleBufferedPropertyInfo), '("events", Gtk.Widget.WidgetEventsPropertyInfo), '("expand", Gtk.Widget.WidgetExpandPropertyInfo), '("focusOnClick", Gtk.Widget.WidgetFocusOnClickPropertyInfo), '("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), '("image", ButtonImagePropertyInfo), '("imagePosition", ButtonImagePositionPropertyInfo), '("isFocus", Gtk.Widget.WidgetIsFocusPropertyInfo), '("label", ButtonLabelPropertyInfo), '("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), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("relatedAction", Gtk.Activatable.ActivatableRelatedActionPropertyInfo), '("relief", ButtonReliefPropertyInfo), '("resizeMode", Gtk.Container.ContainerResizeModePropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("style", Gtk.Widget.WidgetStylePropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("useActionAppearance", Gtk.Activatable.ActivatableUseActionAppearancePropertyInfo), '("useStock", ButtonUseStockPropertyInfo), '("useUnderline", ButtonUseUnderlinePropertyInfo), '("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", ButtonXalignPropertyInfo), '("yalign", ButtonYalignPropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
buttonAlwaysShowImage :: AttrLabelProxy "alwaysShowImage"
buttonAlwaysShowImage = AttrLabelProxy
buttonImage :: AttrLabelProxy "image"
buttonImage = AttrLabelProxy
buttonImagePosition :: AttrLabelProxy "imagePosition"
buttonImagePosition = AttrLabelProxy
buttonLabel :: AttrLabelProxy "label"
buttonLabel = AttrLabelProxy
buttonRelief :: AttrLabelProxy "relief"
buttonRelief = AttrLabelProxy
buttonUseStock :: AttrLabelProxy "useStock"
buttonUseStock = AttrLabelProxy
buttonUseUnderline :: AttrLabelProxy "useUnderline"
buttonUseUnderline = AttrLabelProxy
buttonXalign :: AttrLabelProxy "xalign"
buttonXalign = AttrLabelProxy
buttonYalign :: AttrLabelProxy "yalign"
buttonYalign = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Button = ButtonSignalList
type ButtonSignalList = ('[ '("accelClosuresChanged", Gtk.Widget.WidgetAccelClosuresChangedSignalInfo), '("activate", ButtonActivateSignalInfo), '("add", Gtk.Container.ContainerAddSignalInfo), '("buttonPressEvent", Gtk.Widget.WidgetButtonPressEventSignalInfo), '("buttonReleaseEvent", Gtk.Widget.WidgetButtonReleaseEventSignalInfo), '("canActivateAccel", Gtk.Widget.WidgetCanActivateAccelSignalInfo), '("checkResize", Gtk.Container.ContainerCheckResizeSignalInfo), '("childNotify", Gtk.Widget.WidgetChildNotifySignalInfo), '("clicked", ButtonClickedSignalInfo), '("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), '("enter", ButtonEnterSignalInfo), '("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), '("leave", ButtonLeaveSignalInfo), '("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), '("pressed", ButtonPressedSignalInfo), '("propertyNotifyEvent", Gtk.Widget.WidgetPropertyNotifyEventSignalInfo), '("proximityInEvent", Gtk.Widget.WidgetProximityInEventSignalInfo), '("proximityOutEvent", Gtk.Widget.WidgetProximityOutEventSignalInfo), '("queryTooltip", Gtk.Widget.WidgetQueryTooltipSignalInfo), '("realize", Gtk.Widget.WidgetRealizeSignalInfo), '("released", ButtonReleasedSignalInfo), '("remove", Gtk.Container.ContainerRemoveSignalInfo), '("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), '("setFocusChild", Gtk.Container.ContainerSetFocusChildSignalInfo), '("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
foreign import ccall "gtk_button_new" gtk_button_new :: 
    IO (Ptr Button)
buttonNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Button
    
buttonNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Button
buttonNew  = IO Button -> m Button
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Button -> m Button) -> IO Button -> m Button
forall a b. (a -> b) -> a -> b
$ do
    Ptr Button
result <- IO (Ptr Button)
gtk_button_new
    Text -> Ptr Button -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"buttonNew" Ptr Button
result
    Button
result' <- ((ManagedPtr Button -> Button) -> Ptr Button -> IO Button
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Button -> Button
Button) Ptr Button
result
    Button -> IO Button
forall (m :: * -> *) a. Monad m => a -> m a
return Button
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_button_new_from_icon_name" gtk_button_new_from_icon_name :: 
    CString ->                              
    Int32 ->                                
    IO (Ptr Button)
buttonNewFromIconName ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Maybe (T.Text)
    
    -> Int32
    
    -> m Button
    
buttonNewFromIconName :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Maybe Text -> Int32 -> m Button
buttonNewFromIconName Maybe Text
iconName Int32
size = IO Button -> m Button
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Button -> m Button) -> IO Button -> m Button
forall a b. (a -> b) -> a -> b
$ do
    Ptr CChar
maybeIconName <- case Maybe Text
iconName of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
        Just Text
jIconName -> do
            Ptr CChar
jIconName' <- Text -> IO (Ptr CChar)
textToCString Text
jIconName
            Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jIconName'
    Ptr Button
result <- Ptr CChar -> Int32 -> IO (Ptr Button)
gtk_button_new_from_icon_name Ptr CChar
maybeIconName Int32
size
    Text -> Ptr Button -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"buttonNewFromIconName" Ptr Button
result
    Button
result' <- ((ManagedPtr Button -> Button) -> Ptr Button -> IO Button
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Button -> Button
Button) Ptr Button
result
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeIconName
    Button -> IO Button
forall (m :: * -> *) a. Monad m => a -> m a
return Button
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_button_new_from_stock" gtk_button_new_from_stock :: 
    CString ->                              
    IO (Ptr Button)
{-# DEPRECATED buttonNewFromStock ["(Since version 3.10)","Stock items are deprecated. Use 'GI.Gtk.Objects.Button.buttonNewWithLabel'","instead."] #-}
buttonNewFromStock ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    
    -> m Button
    
buttonNewFromStock :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Text -> m Button
buttonNewFromStock Text
stockId = IO Button -> m Button
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Button -> m Button) -> IO Button -> m Button
forall a b. (a -> b) -> a -> b
$ do
    Ptr CChar
stockId' <- Text -> IO (Ptr CChar)
textToCString Text
stockId
    Ptr Button
result <- Ptr CChar -> IO (Ptr Button)
gtk_button_new_from_stock Ptr CChar
stockId'
    Text -> Ptr Button -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"buttonNewFromStock" Ptr Button
result
    Button
result' <- ((ManagedPtr Button -> Button) -> Ptr Button -> IO Button
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Button -> Button
Button) Ptr Button
result
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
stockId'
    Button -> IO Button
forall (m :: * -> *) a. Monad m => a -> m a
return Button
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_button_new_with_label" gtk_button_new_with_label :: 
    CString ->                              
    IO (Ptr Button)
buttonNewWithLabel ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    
    -> m Button
    
buttonNewWithLabel :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Text -> m Button
buttonNewWithLabel Text
label = IO Button -> m Button
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Button -> m Button) -> IO Button -> m Button
forall a b. (a -> b) -> a -> b
$ do
    Ptr CChar
label' <- Text -> IO (Ptr CChar)
textToCString Text
label
    Ptr Button
result <- Ptr CChar -> IO (Ptr Button)
gtk_button_new_with_label Ptr CChar
label'
    Text -> Ptr Button -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"buttonNewWithLabel" Ptr Button
result
    Button
result' <- ((ManagedPtr Button -> Button) -> Ptr Button -> IO Button
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Button -> Button
Button) Ptr Button
result
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
label'
    Button -> IO Button
forall (m :: * -> *) a. Monad m => a -> m a
return Button
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_button_new_with_mnemonic" gtk_button_new_with_mnemonic :: 
    CString ->                              
    IO (Ptr Button)
buttonNewWithMnemonic ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    
    
    -> m Button
    
buttonNewWithMnemonic :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Text -> m Button
buttonNewWithMnemonic Text
label = IO Button -> m Button
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Button -> m Button) -> IO Button -> m Button
forall a b. (a -> b) -> a -> b
$ do
    Ptr CChar
label' <- Text -> IO (Ptr CChar)
textToCString Text
label
    Ptr Button
result <- Ptr CChar -> IO (Ptr Button)
gtk_button_new_with_mnemonic Ptr CChar
label'
    Text -> Ptr Button -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"buttonNewWithMnemonic" Ptr Button
result
    Button
result' <- ((ManagedPtr Button -> Button) -> Ptr Button -> IO Button
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Button -> Button
Button) Ptr Button
result
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
label'
    Button -> IO Button
forall (m :: * -> *) a. Monad m => a -> m a
return Button
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_button_clicked" gtk_button_clicked :: 
    Ptr Button ->                           
    IO ()
buttonClicked ::
    (B.CallStack.HasCallStack, MonadIO m, IsButton a) =>
    a
    
    -> m ()
buttonClicked :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsButton a) =>
a -> m ()
buttonClicked a
button = 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 Button
button' <- a -> IO (Ptr Button)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
    Ptr Button -> IO ()
gtk_button_clicked Ptr Button
button'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ButtonClickedMethodInfo
instance (signature ~ (m ()), MonadIO m, IsButton a) => O.OverloadedMethod ButtonClickedMethodInfo a signature where
    overloadedMethod = buttonClicked
instance O.OverloadedMethodInfo ButtonClickedMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Button.buttonClicked",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-Button.html#v:buttonClicked"
        }
#endif
foreign import ccall "gtk_button_enter" gtk_button_enter :: 
    Ptr Button ->                           
    IO ()
{-# DEPRECATED buttonEnter ["(Since version 2.20)","Use the [enterNotifyEvent](\"GI.Gtk.Objects.Widget#g:signal:enterNotifyEvent\") signal."] #-}
buttonEnter ::
    (B.CallStack.HasCallStack, MonadIO m, IsButton a) =>
    a
    
    -> m ()
buttonEnter :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsButton a) =>
a -> m ()
buttonEnter a
button = 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 Button
button' <- a -> IO (Ptr Button)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
    Ptr Button -> IO ()
gtk_button_enter Ptr Button
button'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ButtonEnterMethodInfo
instance (signature ~ (m ()), MonadIO m, IsButton a) => O.OverloadedMethod ButtonEnterMethodInfo a signature where
    overloadedMethod = buttonEnter
instance O.OverloadedMethodInfo ButtonEnterMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Button.buttonEnter",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-Button.html#v:buttonEnter"
        }
#endif
foreign import ccall "gtk_button_get_alignment" gtk_button_get_alignment :: 
    Ptr Button ->                           
    Ptr CFloat ->                           
    Ptr CFloat ->                           
    IO ()
{-# DEPRECATED buttonGetAlignment ["(Since version 3.14)","Access the child widget directly if you need to control","its alignment."] #-}
buttonGetAlignment ::
    (B.CallStack.HasCallStack, MonadIO m, IsButton a) =>
    a
    
    -> m ((Float, Float))
buttonGetAlignment :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsButton a) =>
a -> m (Float, Float)
buttonGetAlignment a
button = IO (Float, Float) -> m (Float, Float)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Float, Float) -> m (Float, Float))
-> IO (Float, Float) -> m (Float, Float)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Button
button' <- a -> IO (Ptr Button)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
    Ptr CFloat
xalign <- IO (Ptr CFloat)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CFloat)
    Ptr CFloat
yalign <- IO (Ptr CFloat)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CFloat)
    Ptr Button -> Ptr CFloat -> Ptr CFloat -> IO ()
gtk_button_get_alignment Ptr Button
button' Ptr CFloat
xalign Ptr CFloat
yalign
    CFloat
xalign' <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek Ptr CFloat
xalign
    let xalign'' :: Float
xalign'' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
xalign'
    CFloat
yalign' <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek Ptr CFloat
yalign
    let yalign'' :: Float
yalign'' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
yalign'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
    Ptr CFloat -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CFloat
xalign
    Ptr CFloat -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CFloat
yalign
    (Float, Float) -> IO (Float, Float)
forall (m :: * -> *) a. Monad m => a -> m a
return (Float
xalign'', Float
yalign'')
#if defined(ENABLE_OVERLOADING)
data ButtonGetAlignmentMethodInfo
instance (signature ~ (m ((Float, Float))), MonadIO m, IsButton a) => O.OverloadedMethod ButtonGetAlignmentMethodInfo a signature where
    overloadedMethod = buttonGetAlignment
instance O.OverloadedMethodInfo ButtonGetAlignmentMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Button.buttonGetAlignment",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-Button.html#v:buttonGetAlignment"
        }
#endif
foreign import ccall "gtk_button_get_always_show_image" gtk_button_get_always_show_image :: 
    Ptr Button ->                           
    IO CInt
buttonGetAlwaysShowImage ::
    (B.CallStack.HasCallStack, MonadIO m, IsButton a) =>
    a
    
    -> m Bool
    
buttonGetAlwaysShowImage :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsButton a) =>
a -> m Bool
buttonGetAlwaysShowImage a
button = 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
$ do
    Ptr Button
button' <- a -> IO (Ptr Button)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
    CInt
result <- Ptr Button -> IO CInt
gtk_button_get_always_show_image Ptr Button
button'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data ButtonGetAlwaysShowImageMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsButton a) => O.OverloadedMethod ButtonGetAlwaysShowImageMethodInfo a signature where
    overloadedMethod = buttonGetAlwaysShowImage
instance O.OverloadedMethodInfo ButtonGetAlwaysShowImageMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Button.buttonGetAlwaysShowImage",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-Button.html#v:buttonGetAlwaysShowImage"
        }
#endif
foreign import ccall "gtk_button_get_event_window" gtk_button_get_event_window :: 
    Ptr Button ->                           
    IO (Ptr Gdk.Window.Window)
buttonGetEventWindow ::
    (B.CallStack.HasCallStack, MonadIO m, IsButton a) =>
    a
    
    -> m Gdk.Window.Window
    
buttonGetEventWindow :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsButton a) =>
a -> m Window
buttonGetEventWindow a
button = IO Window -> m Window
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Window -> m Window) -> IO Window -> m Window
forall a b. (a -> b) -> a -> b
$ do
    Ptr Button
button' <- a -> IO (Ptr Button)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
    Ptr Window
result <- Ptr Button -> IO (Ptr Window)
gtk_button_get_event_window Ptr Button
button'
    Text -> Ptr Window -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"buttonGetEventWindow" Ptr Window
result
    Window
result' <- ((ManagedPtr Window -> Window) -> Ptr Window -> IO Window
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Window -> Window
Gdk.Window.Window) Ptr Window
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
    Window -> IO Window
forall (m :: * -> *) a. Monad m => a -> m a
return Window
result'
#if defined(ENABLE_OVERLOADING)
data ButtonGetEventWindowMethodInfo
instance (signature ~ (m Gdk.Window.Window), MonadIO m, IsButton a) => O.OverloadedMethod ButtonGetEventWindowMethodInfo a signature where
    overloadedMethod = buttonGetEventWindow
instance O.OverloadedMethodInfo ButtonGetEventWindowMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Button.buttonGetEventWindow",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-Button.html#v:buttonGetEventWindow"
        }
#endif
foreign import ccall "gtk_button_get_focus_on_click" gtk_button_get_focus_on_click :: 
    Ptr Button ->                           
    IO CInt
{-# DEPRECATED buttonGetFocusOnClick ["(Since version 3.20)","Use 'GI.Gtk.Objects.Widget.widgetGetFocusOnClick' instead"] #-}
buttonGetFocusOnClick ::
    (B.CallStack.HasCallStack, MonadIO m, IsButton a) =>
    a
    
    -> m Bool
    
    
buttonGetFocusOnClick :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsButton a) =>
a -> m Bool
buttonGetFocusOnClick a
button = 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
$ do
    Ptr Button
button' <- a -> IO (Ptr Button)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
    CInt
result <- Ptr Button -> IO CInt
gtk_button_get_focus_on_click Ptr Button
button'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data ButtonGetFocusOnClickMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsButton a) => O.OverloadedMethod ButtonGetFocusOnClickMethodInfo a signature where
    overloadedMethod = buttonGetFocusOnClick
instance O.OverloadedMethodInfo ButtonGetFocusOnClickMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Button.buttonGetFocusOnClick",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-Button.html#v:buttonGetFocusOnClick"
        }
#endif
foreign import ccall "gtk_button_get_image" gtk_button_get_image :: 
    Ptr Button ->                           
    IO (Ptr Gtk.Widget.Widget)
buttonGetImage ::
    (B.CallStack.HasCallStack, MonadIO m, IsButton a) =>
    a
    
    -> m (Maybe Gtk.Widget.Widget)
    
    
buttonGetImage :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsButton a) =>
a -> m (Maybe Widget)
buttonGetImage a
button = IO (Maybe Widget) -> m (Maybe Widget)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Widget) -> m (Maybe Widget))
-> IO (Maybe Widget) -> m (Maybe Widget)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Button
button' <- a -> IO (Ptr Button)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
    Ptr Widget
result <- Ptr Button -> IO (Ptr Widget)
gtk_button_get_image Ptr Button
button'
    Maybe Widget
maybeResult <- Ptr Widget -> (Ptr Widget -> IO Widget) -> IO (Maybe Widget)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Widget
result ((Ptr Widget -> IO Widget) -> IO (Maybe Widget))
-> (Ptr Widget -> IO Widget) -> IO (Maybe Widget)
forall a b. (a -> b) -> a -> b
$ \Ptr Widget
result' -> do
        Widget
result'' <- ((ManagedPtr Widget -> Widget) -> Ptr Widget -> IO Widget
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Widget -> Widget
Gtk.Widget.Widget) Ptr Widget
result'
        Widget -> IO Widget
forall (m :: * -> *) a. Monad m => a -> m a
return Widget
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
    Maybe Widget -> IO (Maybe Widget)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Widget
maybeResult
#if defined(ENABLE_OVERLOADING)
data ButtonGetImageMethodInfo
instance (signature ~ (m (Maybe Gtk.Widget.Widget)), MonadIO m, IsButton a) => O.OverloadedMethod ButtonGetImageMethodInfo a signature where
    overloadedMethod = buttonGetImage
instance O.OverloadedMethodInfo ButtonGetImageMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Button.buttonGetImage",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-Button.html#v:buttonGetImage"
        }
#endif
foreign import ccall "gtk_button_get_image_position" gtk_button_get_image_position :: 
    Ptr Button ->                           
    IO CUInt
buttonGetImagePosition ::
    (B.CallStack.HasCallStack, MonadIO m, IsButton a) =>
    a
    
    -> m Gtk.Enums.PositionType
    
buttonGetImagePosition :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsButton a) =>
a -> m PositionType
buttonGetImagePosition a
button = IO PositionType -> m PositionType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PositionType -> m PositionType)
-> IO PositionType -> m PositionType
forall a b. (a -> b) -> a -> b
$ do
    Ptr Button
button' <- a -> IO (Ptr Button)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
    CUInt
result <- Ptr Button -> IO CUInt
gtk_button_get_image_position Ptr Button
button'
    let result' :: PositionType
result' = (Int -> PositionType
forall a. Enum a => Int -> a
toEnum (Int -> PositionType) -> (CUInt -> Int) -> CUInt -> PositionType
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
button
    PositionType -> IO PositionType
forall (m :: * -> *) a. Monad m => a -> m a
return PositionType
result'
#if defined(ENABLE_OVERLOADING)
data ButtonGetImagePositionMethodInfo
instance (signature ~ (m Gtk.Enums.PositionType), MonadIO m, IsButton a) => O.OverloadedMethod ButtonGetImagePositionMethodInfo a signature where
    overloadedMethod = buttonGetImagePosition
instance O.OverloadedMethodInfo ButtonGetImagePositionMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Button.buttonGetImagePosition",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-Button.html#v:buttonGetImagePosition"
        }
#endif
foreign import ccall "gtk_button_get_label" gtk_button_get_label :: 
    Ptr Button ->                           
    IO CString
buttonGetLabel ::
    (B.CallStack.HasCallStack, MonadIO m, IsButton a) =>
    a
    
    -> m T.Text
    
    
buttonGetLabel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsButton a) =>
a -> m Text
buttonGetLabel a
button = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr Button
button' <- a -> IO (Ptr Button)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
    Ptr CChar
result <- Ptr Button -> IO (Ptr CChar)
gtk_button_get_label Ptr Button
button'
    Text -> Ptr CChar -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"buttonGetLabel" Ptr CChar
result
    Text
result' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data ButtonGetLabelMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsButton a) => O.OverloadedMethod ButtonGetLabelMethodInfo a signature where
    overloadedMethod = buttonGetLabel
instance O.OverloadedMethodInfo ButtonGetLabelMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Button.buttonGetLabel",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-Button.html#v:buttonGetLabel"
        }
#endif
foreign import ccall "gtk_button_get_relief" gtk_button_get_relief :: 
    Ptr Button ->                           
    IO CUInt
buttonGetRelief ::
    (B.CallStack.HasCallStack, MonadIO m, IsButton a) =>
    a
    
    -> m Gtk.Enums.ReliefStyle
    
buttonGetRelief :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsButton a) =>
a -> m ReliefStyle
buttonGetRelief a
button = IO ReliefStyle -> m ReliefStyle
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ReliefStyle -> m ReliefStyle)
-> IO ReliefStyle -> m ReliefStyle
forall a b. (a -> b) -> a -> b
$ do
    Ptr Button
button' <- a -> IO (Ptr Button)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
    CUInt
result <- Ptr Button -> IO CUInt
gtk_button_get_relief Ptr Button
button'
    let result' :: ReliefStyle
result' = (Int -> ReliefStyle
forall a. Enum a => Int -> a
toEnum (Int -> ReliefStyle) -> (CUInt -> Int) -> CUInt -> ReliefStyle
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
button
    ReliefStyle -> IO ReliefStyle
forall (m :: * -> *) a. Monad m => a -> m a
return ReliefStyle
result'
#if defined(ENABLE_OVERLOADING)
data ButtonGetReliefMethodInfo
instance (signature ~ (m Gtk.Enums.ReliefStyle), MonadIO m, IsButton a) => O.OverloadedMethod ButtonGetReliefMethodInfo a signature where
    overloadedMethod = buttonGetRelief
instance O.OverloadedMethodInfo ButtonGetReliefMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Button.buttonGetRelief",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-Button.html#v:buttonGetRelief"
        }
#endif
foreign import ccall "gtk_button_get_use_stock" gtk_button_get_use_stock :: 
    Ptr Button ->                           
    IO CInt
{-# DEPRECATED buttonGetUseStock ["(Since version 3.10)"] #-}
buttonGetUseStock ::
    (B.CallStack.HasCallStack, MonadIO m, IsButton a) =>
    a
    
    -> m Bool
    
    
    
buttonGetUseStock :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsButton a) =>
a -> m Bool
buttonGetUseStock a
button = 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
$ do
    Ptr Button
button' <- a -> IO (Ptr Button)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
    CInt
result <- Ptr Button -> IO CInt
gtk_button_get_use_stock Ptr Button
button'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data ButtonGetUseStockMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsButton a) => O.OverloadedMethod ButtonGetUseStockMethodInfo a signature where
    overloadedMethod = buttonGetUseStock
instance O.OverloadedMethodInfo ButtonGetUseStockMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Button.buttonGetUseStock",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-Button.html#v:buttonGetUseStock"
        }
#endif
foreign import ccall "gtk_button_get_use_underline" gtk_button_get_use_underline :: 
    Ptr Button ->                           
    IO CInt
buttonGetUseUnderline ::
    (B.CallStack.HasCallStack, MonadIO m, IsButton a) =>
    a
    
    -> m Bool
    
    
buttonGetUseUnderline :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsButton a) =>
a -> m Bool
buttonGetUseUnderline a
button = 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
$ do
    Ptr Button
button' <- a -> IO (Ptr Button)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
    CInt
result <- Ptr Button -> IO CInt
gtk_button_get_use_underline Ptr Button
button'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data ButtonGetUseUnderlineMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsButton a) => O.OverloadedMethod ButtonGetUseUnderlineMethodInfo a signature where
    overloadedMethod = buttonGetUseUnderline
instance O.OverloadedMethodInfo ButtonGetUseUnderlineMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Button.buttonGetUseUnderline",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-Button.html#v:buttonGetUseUnderline"
        }
#endif
foreign import ccall "gtk_button_leave" gtk_button_leave :: 
    Ptr Button ->                           
    IO ()
{-# DEPRECATED buttonLeave ["(Since version 2.20)","Use the [leaveNotifyEvent](\"GI.Gtk.Objects.Widget#g:signal:leaveNotifyEvent\") signal."] #-}
buttonLeave ::
    (B.CallStack.HasCallStack, MonadIO m, IsButton a) =>
    a
    
    -> m ()
buttonLeave :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsButton a) =>
a -> m ()
buttonLeave a
button = 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 Button
button' <- a -> IO (Ptr Button)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
    Ptr Button -> IO ()
gtk_button_leave Ptr Button
button'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ButtonLeaveMethodInfo
instance (signature ~ (m ()), MonadIO m, IsButton a) => O.OverloadedMethod ButtonLeaveMethodInfo a signature where
    overloadedMethod = buttonLeave
instance O.OverloadedMethodInfo ButtonLeaveMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Button.buttonLeave",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-Button.html#v:buttonLeave"
        }
#endif
foreign import ccall "gtk_button_pressed" gtk_button_pressed :: 
    Ptr Button ->                           
    IO ()
{-# DEPRECATED buttonPressed ["(Since version 2.20)","Use the [buttonPressEvent](\"GI.Gtk.Objects.Widget#g:signal:buttonPressEvent\") signal."] #-}
buttonPressed ::
    (B.CallStack.HasCallStack, MonadIO m, IsButton a) =>
    a
    
    -> m ()
buttonPressed :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsButton a) =>
a -> m ()
buttonPressed a
button = 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 Button
button' <- a -> IO (Ptr Button)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
    Ptr Button -> IO ()
gtk_button_pressed Ptr Button
button'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ButtonPressedMethodInfo
instance (signature ~ (m ()), MonadIO m, IsButton a) => O.OverloadedMethod ButtonPressedMethodInfo a signature where
    overloadedMethod = buttonPressed
instance O.OverloadedMethodInfo ButtonPressedMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Button.buttonPressed",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-Button.html#v:buttonPressed"
        }
#endif
foreign import ccall "gtk_button_released" gtk_button_released :: 
    Ptr Button ->                           
    IO ()
{-# DEPRECATED buttonReleased ["(Since version 2.20)","Use the [buttonReleaseEvent](\"GI.Gtk.Objects.Widget#g:signal:buttonReleaseEvent\") signal."] #-}
buttonReleased ::
    (B.CallStack.HasCallStack, MonadIO m, IsButton a) =>
    a
    
    -> m ()
buttonReleased :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsButton a) =>
a -> m ()
buttonReleased a
button = 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 Button
button' <- a -> IO (Ptr Button)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
    Ptr Button -> IO ()
gtk_button_released Ptr Button
button'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ButtonReleasedMethodInfo
instance (signature ~ (m ()), MonadIO m, IsButton a) => O.OverloadedMethod ButtonReleasedMethodInfo a signature where
    overloadedMethod = buttonReleased
instance O.OverloadedMethodInfo ButtonReleasedMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Button.buttonReleased",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-Button.html#v:buttonReleased"
        }
#endif
foreign import ccall "gtk_button_set_alignment" gtk_button_set_alignment :: 
    Ptr Button ->                           
    CFloat ->                               
    CFloat ->                               
    IO ()
{-# DEPRECATED buttonSetAlignment ["(Since version 3.14)","Access the child widget directly if you need to control","its alignment."] #-}
buttonSetAlignment ::
    (B.CallStack.HasCallStack, MonadIO m, IsButton a) =>
    a
    
    -> Float
    
    
    -> Float
    
    
    -> m ()
buttonSetAlignment :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsButton a) =>
a -> Float -> Float -> m ()
buttonSetAlignment a
button Float
xalign Float
yalign = 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 Button
button' <- a -> IO (Ptr Button)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
    let xalign' :: CFloat
xalign' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
xalign
    let yalign' :: CFloat
yalign' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
yalign
    Ptr Button -> CFloat -> CFloat -> IO ()
gtk_button_set_alignment Ptr Button
button' CFloat
xalign' CFloat
yalign'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ButtonSetAlignmentMethodInfo
instance (signature ~ (Float -> Float -> m ()), MonadIO m, IsButton a) => O.OverloadedMethod ButtonSetAlignmentMethodInfo a signature where
    overloadedMethod = buttonSetAlignment
instance O.OverloadedMethodInfo ButtonSetAlignmentMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Button.buttonSetAlignment",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-Button.html#v:buttonSetAlignment"
        }
#endif
foreign import ccall "gtk_button_set_always_show_image" gtk_button_set_always_show_image :: 
    Ptr Button ->                           
    CInt ->                                 
    IO ()
buttonSetAlwaysShowImage ::
    (B.CallStack.HasCallStack, MonadIO m, IsButton a) =>
    a
    
    -> Bool
    
    -> m ()
buttonSetAlwaysShowImage :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsButton a) =>
a -> Bool -> m ()
buttonSetAlwaysShowImage a
button Bool
alwaysShow = 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 Button
button' <- a -> IO (Ptr Button)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
    let alwaysShow' :: CInt
alwaysShow' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
alwaysShow
    Ptr Button -> CInt -> IO ()
gtk_button_set_always_show_image Ptr Button
button' CInt
alwaysShow'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ButtonSetAlwaysShowImageMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsButton a) => O.OverloadedMethod ButtonSetAlwaysShowImageMethodInfo a signature where
    overloadedMethod = buttonSetAlwaysShowImage
instance O.OverloadedMethodInfo ButtonSetAlwaysShowImageMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Button.buttonSetAlwaysShowImage",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-Button.html#v:buttonSetAlwaysShowImage"
        }
#endif
foreign import ccall "gtk_button_set_focus_on_click" gtk_button_set_focus_on_click :: 
    Ptr Button ->                           
    CInt ->                                 
    IO ()
{-# DEPRECATED buttonSetFocusOnClick ["(Since version 3.20)","Use 'GI.Gtk.Objects.Widget.widgetSetFocusOnClick' instead"] #-}
buttonSetFocusOnClick ::
    (B.CallStack.HasCallStack, MonadIO m, IsButton a) =>
    a
    
    -> Bool
    
    -> m ()
buttonSetFocusOnClick :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsButton a) =>
a -> Bool -> m ()
buttonSetFocusOnClick a
button Bool
focusOnClick = 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 Button
button' <- a -> IO (Ptr Button)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
    let focusOnClick' :: CInt
focusOnClick' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
focusOnClick
    Ptr Button -> CInt -> IO ()
gtk_button_set_focus_on_click Ptr Button
button' CInt
focusOnClick'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ButtonSetFocusOnClickMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsButton a) => O.OverloadedMethod ButtonSetFocusOnClickMethodInfo a signature where
    overloadedMethod = buttonSetFocusOnClick
instance O.OverloadedMethodInfo ButtonSetFocusOnClickMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Button.buttonSetFocusOnClick",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-Button.html#v:buttonSetFocusOnClick"
        }
#endif
foreign import ccall "gtk_button_set_image" gtk_button_set_image :: 
    Ptr Button ->                           
    Ptr Gtk.Widget.Widget ->                
    IO ()
buttonSetImage ::
    (B.CallStack.HasCallStack, MonadIO m, IsButton a, Gtk.Widget.IsWidget b) =>
    a
    
    -> Maybe (b)
    
    -> m ()
buttonSetImage :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsButton a, IsWidget b) =>
a -> Maybe b -> m ()
buttonSetImage a
button Maybe b
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 Button
button' <- a -> IO (Ptr Button)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
    Ptr Widget
maybeImage <- case Maybe b
image of
        Maybe b
Nothing -> Ptr Widget -> IO (Ptr Widget)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
forall a. Ptr a
nullPtr
        Just b
jImage -> do
            Ptr Widget
jImage' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jImage
            Ptr Widget -> IO (Ptr Widget)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
jImage'
    Ptr Button -> Ptr Widget -> IO ()
gtk_button_set_image Ptr Button
button' Ptr Widget
maybeImage
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
image b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ButtonSetImageMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsButton a, Gtk.Widget.IsWidget b) => O.OverloadedMethod ButtonSetImageMethodInfo a signature where
    overloadedMethod = buttonSetImage
instance O.OverloadedMethodInfo ButtonSetImageMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Button.buttonSetImage",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-Button.html#v:buttonSetImage"
        }
#endif
foreign import ccall "gtk_button_set_image_position" gtk_button_set_image_position :: 
    Ptr Button ->                           
    CUInt ->                                
    IO ()
buttonSetImagePosition ::
    (B.CallStack.HasCallStack, MonadIO m, IsButton a) =>
    a
    
    -> Gtk.Enums.PositionType
    
    -> m ()
buttonSetImagePosition :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsButton a) =>
a -> PositionType -> m ()
buttonSetImagePosition a
button PositionType
position = 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 Button
button' <- a -> IO (Ptr Button)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
    let position' :: CUInt
position' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (PositionType -> Int) -> PositionType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PositionType -> Int
forall a. Enum a => a -> Int
fromEnum) PositionType
position
    Ptr Button -> CUInt -> IO ()
gtk_button_set_image_position Ptr Button
button' CUInt
position'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ButtonSetImagePositionMethodInfo
instance (signature ~ (Gtk.Enums.PositionType -> m ()), MonadIO m, IsButton a) => O.OverloadedMethod ButtonSetImagePositionMethodInfo a signature where
    overloadedMethod = buttonSetImagePosition
instance O.OverloadedMethodInfo ButtonSetImagePositionMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Button.buttonSetImagePosition",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-Button.html#v:buttonSetImagePosition"
        }
#endif
foreign import ccall "gtk_button_set_label" gtk_button_set_label :: 
    Ptr Button ->                           
    CString ->                              
    IO ()
buttonSetLabel ::
    (B.CallStack.HasCallStack, MonadIO m, IsButton a) =>
    a
    
    -> T.Text
    
    -> m ()
buttonSetLabel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsButton a) =>
a -> Text -> m ()
buttonSetLabel a
button Text
label = 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 Button
button' <- a -> IO (Ptr Button)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
    Ptr CChar
label' <- Text -> IO (Ptr CChar)
textToCString Text
label
    Ptr Button -> Ptr CChar -> IO ()
gtk_button_set_label Ptr Button
button' Ptr CChar
label'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
label'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ButtonSetLabelMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsButton a) => O.OverloadedMethod ButtonSetLabelMethodInfo a signature where
    overloadedMethod = buttonSetLabel
instance O.OverloadedMethodInfo ButtonSetLabelMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Button.buttonSetLabel",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-Button.html#v:buttonSetLabel"
        }
#endif
foreign import ccall "gtk_button_set_relief" gtk_button_set_relief :: 
    Ptr Button ->                           
    CUInt ->                                
    IO ()
buttonSetRelief ::
    (B.CallStack.HasCallStack, MonadIO m, IsButton a) =>
    a
    
    -> Gtk.Enums.ReliefStyle
    
    -> m ()
buttonSetRelief :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsButton a) =>
a -> ReliefStyle -> m ()
buttonSetRelief a
button ReliefStyle
relief = 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 Button
button' <- a -> IO (Ptr Button)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
    let relief' :: CUInt
relief' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (ReliefStyle -> Int) -> ReliefStyle -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReliefStyle -> Int
forall a. Enum a => a -> Int
fromEnum) ReliefStyle
relief
    Ptr Button -> CUInt -> IO ()
gtk_button_set_relief Ptr Button
button' CUInt
relief'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ButtonSetReliefMethodInfo
instance (signature ~ (Gtk.Enums.ReliefStyle -> m ()), MonadIO m, IsButton a) => O.OverloadedMethod ButtonSetReliefMethodInfo a signature where
    overloadedMethod = buttonSetRelief
instance O.OverloadedMethodInfo ButtonSetReliefMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Button.buttonSetRelief",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-Button.html#v:buttonSetRelief"
        }
#endif
foreign import ccall "gtk_button_set_use_stock" gtk_button_set_use_stock :: 
    Ptr Button ->                           
    CInt ->                                 
    IO ()
{-# DEPRECATED buttonSetUseStock ["(Since version 3.10)"] #-}
buttonSetUseStock ::
    (B.CallStack.HasCallStack, MonadIO m, IsButton a) =>
    a
    
    -> Bool
    
    -> m ()
buttonSetUseStock :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsButton a) =>
a -> Bool -> m ()
buttonSetUseStock a
button Bool
useStock = 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 Button
button' <- a -> IO (Ptr Button)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
    let useStock' :: CInt
useStock' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
useStock
    Ptr Button -> CInt -> IO ()
gtk_button_set_use_stock Ptr Button
button' CInt
useStock'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ButtonSetUseStockMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsButton a) => O.OverloadedMethod ButtonSetUseStockMethodInfo a signature where
    overloadedMethod = buttonSetUseStock
instance O.OverloadedMethodInfo ButtonSetUseStockMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Button.buttonSetUseStock",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-Button.html#v:buttonSetUseStock"
        }
#endif
foreign import ccall "gtk_button_set_use_underline" gtk_button_set_use_underline :: 
    Ptr Button ->                           
    CInt ->                                 
    IO ()
buttonSetUseUnderline ::
    (B.CallStack.HasCallStack, MonadIO m, IsButton a) =>
    a
    
    -> Bool
    
    -> m ()
buttonSetUseUnderline :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsButton a) =>
a -> Bool -> m ()
buttonSetUseUnderline a
button Bool
useUnderline = 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 Button
button' <- a -> IO (Ptr Button)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
    let useUnderline' :: CInt
useUnderline' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
useUnderline
    Ptr Button -> CInt -> IO ()
gtk_button_set_use_underline Ptr Button
button' CInt
useUnderline'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ButtonSetUseUnderlineMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsButton a) => O.OverloadedMethod ButtonSetUseUnderlineMethodInfo a signature where
    overloadedMethod = buttonSetUseUnderline
instance O.OverloadedMethodInfo ButtonSetUseUnderlineMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Button.buttonSetUseUnderline",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-Button.html#v:buttonSetUseUnderline"
        }
#endif