{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Interfaces.Actionable
(
Actionable(..) ,
IsActionable ,
toActionable ,
#if defined(ENABLE_OVERLOADING)
ResolveActionableMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
ActionableGetActionNameMethodInfo ,
#endif
actionableGetActionName ,
#if defined(ENABLE_OVERLOADING)
ActionableGetActionTargetValueMethodInfo,
#endif
actionableGetActionTargetValue ,
#if defined(ENABLE_OVERLOADING)
ActionableSetActionNameMethodInfo ,
#endif
actionableSetActionName ,
#if defined(ENABLE_OVERLOADING)
ActionableSetActionTargetValueMethodInfo,
#endif
actionableSetActionTargetValue ,
#if defined(ENABLE_OVERLOADING)
ActionableSetDetailedActionNameMethodInfo,
#endif
actionableSetDetailedActionName ,
#if defined(ENABLE_OVERLOADING)
ActionableActionNamePropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
actionableActionName ,
#endif
clearActionableActionName ,
constructActionableActionName ,
getActionableActionName ,
setActionableActionName ,
#if defined(ENABLE_OVERLOADING)
ActionableActionTargetPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
actionableActionTarget ,
#endif
clearActionableActionTarget ,
constructActionableActionTarget ,
getActionableActionTarget ,
setActionableActionTarget ,
) 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 GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget
newtype Actionable = Actionable (SP.ManagedPtr Actionable)
deriving (Actionable -> Actionable -> Bool
(Actionable -> Actionable -> Bool)
-> (Actionable -> Actionable -> Bool) -> Eq Actionable
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Actionable -> Actionable -> Bool
$c/= :: Actionable -> Actionable -> Bool
== :: Actionable -> Actionable -> Bool
$c== :: Actionable -> Actionable -> Bool
Eq)
instance SP.ManagedPtrNewtype Actionable where
toManagedPtr :: Actionable -> ManagedPtr Actionable
toManagedPtr (Actionable ManagedPtr Actionable
p) = ManagedPtr Actionable
p
foreign import ccall "gtk_actionable_get_type"
c_gtk_actionable_get_type :: IO B.Types.GType
instance B.Types.TypedObject Actionable where
glibType :: IO GType
glibType = IO GType
c_gtk_actionable_get_type
instance B.Types.GObject Actionable
instance B.GValue.IsGValue Actionable where
toGValue :: Actionable -> IO GValue
toGValue Actionable
o = do
GType
gtype <- IO GType
c_gtk_actionable_get_type
Actionable -> (Ptr Actionable -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Actionable
o (GType
-> (GValue -> Ptr Actionable -> IO ())
-> Ptr Actionable
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr Actionable -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO Actionable
fromGValue GValue
gv = do
Ptr Actionable
ptr <- GValue -> IO (Ptr Actionable)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr Actionable)
(ManagedPtr Actionable -> Actionable)
-> Ptr Actionable -> IO Actionable
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Actionable -> Actionable
Actionable Ptr Actionable
ptr
class (SP.GObject o, O.IsDescendantOf Actionable o) => IsActionable o
instance (SP.GObject o, O.IsDescendantOf Actionable o) => IsActionable o
instance O.HasParentTypes Actionable
type instance O.ParentTypes Actionable = '[GObject.Object.Object, Gtk.Widget.Widget]
toActionable :: (MonadIO m, IsActionable o) => o -> m Actionable
toActionable :: o -> m Actionable
toActionable = IO Actionable -> m Actionable
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Actionable -> m Actionable)
-> (o -> IO Actionable) -> o -> m Actionable
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Actionable -> Actionable) -> o -> IO Actionable
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr Actionable -> Actionable
Actionable
getActionableActionName :: (MonadIO m, IsActionable o) => o -> m (Maybe T.Text)
getActionableActionName :: o -> m (Maybe Text)
getActionableActionName o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"action-name"
setActionableActionName :: (MonadIO m, IsActionable o) => o -> T.Text -> m ()
setActionableActionName :: o -> Text -> m ()
setActionableActionName o
obj Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"action-name" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructActionableActionName :: (IsActionable o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructActionableActionName :: Text -> m (GValueConstruct o)
constructActionableActionName 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
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"action-name" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
clearActionableActionName :: (MonadIO m, IsActionable o) => o -> m ()
clearActionableActionName :: o -> m ()
clearActionableActionName o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"action-name" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)
#if defined(ENABLE_OVERLOADING)
data ActionableActionNamePropertyInfo
instance AttrInfo ActionableActionNamePropertyInfo where
type AttrAllowedOps ActionableActionNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint ActionableActionNamePropertyInfo = IsActionable
type AttrSetTypeConstraint ActionableActionNamePropertyInfo = (~) T.Text
type AttrTransferTypeConstraint ActionableActionNamePropertyInfo = (~) T.Text
type AttrTransferType ActionableActionNamePropertyInfo = T.Text
type AttrGetType ActionableActionNamePropertyInfo = (Maybe T.Text)
type AttrLabel ActionableActionNamePropertyInfo = "action-name"
type AttrOrigin ActionableActionNamePropertyInfo = Actionable
attrGet = getActionableActionName
attrSet = setActionableActionName
attrTransfer _ v = do
return v
attrConstruct = constructActionableActionName
attrClear = clearActionableActionName
#endif
getActionableActionTarget :: (MonadIO m, IsActionable o) => o -> m (Maybe GVariant)
getActionableActionTarget :: o -> m (Maybe GVariant)
getActionableActionTarget o
obj = IO (Maybe GVariant) -> m (Maybe GVariant)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe GVariant) -> m (Maybe GVariant))
-> IO (Maybe GVariant) -> m (Maybe GVariant)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe GVariant)
forall a. GObject a => a -> String -> IO (Maybe GVariant)
B.Properties.getObjectPropertyVariant o
obj String
"action-target"
setActionableActionTarget :: (MonadIO m, IsActionable o) => o -> GVariant -> m ()
setActionableActionTarget :: o -> GVariant -> m ()
setActionableActionTarget o
obj GVariant
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe GVariant -> IO ()
forall a. GObject a => a -> String -> Maybe GVariant -> IO ()
B.Properties.setObjectPropertyVariant o
obj String
"action-target" (GVariant -> Maybe GVariant
forall a. a -> Maybe a
Just GVariant
val)
constructActionableActionTarget :: (IsActionable o, MIO.MonadIO m) => GVariant -> m (GValueConstruct o)
constructActionableActionTarget :: GVariant -> m (GValueConstruct o)
constructActionableActionTarget GVariant
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
$ String -> Maybe GVariant -> IO (GValueConstruct o)
forall o. String -> Maybe GVariant -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyVariant String
"action-target" (GVariant -> Maybe GVariant
forall a. a -> Maybe a
P.Just GVariant
val)
clearActionableActionTarget :: (MonadIO m, IsActionable o) => o -> m ()
clearActionableActionTarget :: o -> m ()
clearActionableActionTarget 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 GVariant -> IO ()
forall a. GObject a => a -> String -> Maybe GVariant -> IO ()
B.Properties.setObjectPropertyVariant o
obj String
"action-target" (Maybe GVariant
forall a. Maybe a
Nothing :: Maybe GVariant)
#if defined(ENABLE_OVERLOADING)
data ActionableActionTargetPropertyInfo
instance AttrInfo ActionableActionTargetPropertyInfo where
type AttrAllowedOps ActionableActionTargetPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint ActionableActionTargetPropertyInfo = IsActionable
type AttrSetTypeConstraint ActionableActionTargetPropertyInfo = (~) GVariant
type AttrTransferTypeConstraint ActionableActionTargetPropertyInfo = (~) GVariant
type AttrTransferType ActionableActionTargetPropertyInfo = GVariant
type AttrGetType ActionableActionTargetPropertyInfo = (Maybe GVariant)
type AttrLabel ActionableActionTargetPropertyInfo = "action-target"
type AttrOrigin ActionableActionTargetPropertyInfo = Actionable
attrGet = getActionableActionTarget
attrSet = setActionableActionTarget
attrTransfer _ v = do
return v
attrConstruct = constructActionableActionTarget
attrClear = clearActionableActionTarget
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Actionable
type instance O.AttributeList Actionable = ActionableAttributeList
type ActionableAttributeList = ('[ '("actionName", ActionableActionNamePropertyInfo), '("actionTarget", ActionableActionTargetPropertyInfo), '("appPaintable", Gtk.Widget.WidgetAppPaintablePropertyInfo), '("canDefault", Gtk.Widget.WidgetCanDefaultPropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("compositeChild", Gtk.Widget.WidgetCompositeChildPropertyInfo), '("doubleBuffered", Gtk.Widget.WidgetDoubleBufferedPropertyInfo), '("events", Gtk.Widget.WidgetEventsPropertyInfo), '("expand", Gtk.Widget.WidgetExpandPropertyInfo), '("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), '("isFocus", Gtk.Widget.WidgetIsFocusPropertyInfo), '("margin", Gtk.Widget.WidgetMarginPropertyInfo), '("marginBottom", Gtk.Widget.WidgetMarginBottomPropertyInfo), '("marginEnd", Gtk.Widget.WidgetMarginEndPropertyInfo), '("marginLeft", Gtk.Widget.WidgetMarginLeftPropertyInfo), '("marginRight", Gtk.Widget.WidgetMarginRightPropertyInfo), '("marginStart", Gtk.Widget.WidgetMarginStartPropertyInfo), '("marginTop", Gtk.Widget.WidgetMarginTopPropertyInfo), '("name", Gtk.Widget.WidgetNamePropertyInfo), '("noShowAll", Gtk.Widget.WidgetNoShowAllPropertyInfo), '("opacity", Gtk.Widget.WidgetOpacityPropertyInfo), '("parent", Gtk.Widget.WidgetParentPropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("style", Gtk.Widget.WidgetStylePropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("valign", Gtk.Widget.WidgetValignPropertyInfo), '("vexpand", Gtk.Widget.WidgetVexpandPropertyInfo), '("vexpandSet", Gtk.Widget.WidgetVexpandSetPropertyInfo), '("visible", Gtk.Widget.WidgetVisiblePropertyInfo), '("widthRequest", Gtk.Widget.WidgetWidthRequestPropertyInfo), '("window", Gtk.Widget.WidgetWindowPropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
actionableActionName :: AttrLabelProxy "actionName"
actionableActionName = AttrLabelProxy
actionableActionTarget :: AttrLabelProxy "actionTarget"
actionableActionTarget = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveActionableMethod (t :: Symbol) (o :: *) :: * where
ResolveActionableMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
ResolveActionableMethod "addAccelerator" o = Gtk.Widget.WidgetAddAcceleratorMethodInfo
ResolveActionableMethod "addChild" o = Gtk.Buildable.BuildableAddChildMethodInfo
ResolveActionableMethod "addDeviceEvents" o = Gtk.Widget.WidgetAddDeviceEventsMethodInfo
ResolveActionableMethod "addEvents" o = Gtk.Widget.WidgetAddEventsMethodInfo
ResolveActionableMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
ResolveActionableMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
ResolveActionableMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveActionableMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveActionableMethod "canActivateAccel" o = Gtk.Widget.WidgetCanActivateAccelMethodInfo
ResolveActionableMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
ResolveActionableMethod "childNotify" o = Gtk.Widget.WidgetChildNotifyMethodInfo
ResolveActionableMethod "classPath" o = Gtk.Widget.WidgetClassPathMethodInfo
ResolveActionableMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
ResolveActionableMethod "constructChild" o = Gtk.Buildable.BuildableConstructChildMethodInfo
ResolveActionableMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
ResolveActionableMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
ResolveActionableMethod "customFinished" o = Gtk.Buildable.BuildableCustomFinishedMethodInfo
ResolveActionableMethod "customTagEnd" o = Gtk.Buildable.BuildableCustomTagEndMethodInfo
ResolveActionableMethod "customTagStart" o = Gtk.Buildable.BuildableCustomTagStartMethodInfo
ResolveActionableMethod "destroy" o = Gtk.Widget.WidgetDestroyMethodInfo
ResolveActionableMethod "destroyed" o = Gtk.Widget.WidgetDestroyedMethodInfo
ResolveActionableMethod "deviceIsShadowed" o = Gtk.Widget.WidgetDeviceIsShadowedMethodInfo
ResolveActionableMethod "dragBegin" o = Gtk.Widget.WidgetDragBeginMethodInfo
ResolveActionableMethod "dragBeginWithCoordinates" o = Gtk.Widget.WidgetDragBeginWithCoordinatesMethodInfo
ResolveActionableMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
ResolveActionableMethod "dragDestAddImageTargets" o = Gtk.Widget.WidgetDragDestAddImageTargetsMethodInfo
ResolveActionableMethod "dragDestAddTextTargets" o = Gtk.Widget.WidgetDragDestAddTextTargetsMethodInfo
ResolveActionableMethod "dragDestAddUriTargets" o = Gtk.Widget.WidgetDragDestAddUriTargetsMethodInfo
ResolveActionableMethod "dragDestFindTarget" o = Gtk.Widget.WidgetDragDestFindTargetMethodInfo
ResolveActionableMethod "dragDestGetTargetList" o = Gtk.Widget.WidgetDragDestGetTargetListMethodInfo
ResolveActionableMethod "dragDestGetTrackMotion" o = Gtk.Widget.WidgetDragDestGetTrackMotionMethodInfo
ResolveActionableMethod "dragDestSet" o = Gtk.Widget.WidgetDragDestSetMethodInfo
ResolveActionableMethod "dragDestSetProxy" o = Gtk.Widget.WidgetDragDestSetProxyMethodInfo
ResolveActionableMethod "dragDestSetTargetList" o = Gtk.Widget.WidgetDragDestSetTargetListMethodInfo
ResolveActionableMethod "dragDestSetTrackMotion" o = Gtk.Widget.WidgetDragDestSetTrackMotionMethodInfo
ResolveActionableMethod "dragDestUnset" o = Gtk.Widget.WidgetDragDestUnsetMethodInfo
ResolveActionableMethod "dragGetData" o = Gtk.Widget.WidgetDragGetDataMethodInfo
ResolveActionableMethod "dragHighlight" o = Gtk.Widget.WidgetDragHighlightMethodInfo
ResolveActionableMethod "dragSourceAddImageTargets" o = Gtk.Widget.WidgetDragSourceAddImageTargetsMethodInfo
ResolveActionableMethod "dragSourceAddTextTargets" o = Gtk.Widget.WidgetDragSourceAddTextTargetsMethodInfo
ResolveActionableMethod "dragSourceAddUriTargets" o = Gtk.Widget.WidgetDragSourceAddUriTargetsMethodInfo
ResolveActionableMethod "dragSourceGetTargetList" o = Gtk.Widget.WidgetDragSourceGetTargetListMethodInfo
ResolveActionableMethod "dragSourceSet" o = Gtk.Widget.WidgetDragSourceSetMethodInfo
ResolveActionableMethod "dragSourceSetIconGicon" o = Gtk.Widget.WidgetDragSourceSetIconGiconMethodInfo
ResolveActionableMethod "dragSourceSetIconName" o = Gtk.Widget.WidgetDragSourceSetIconNameMethodInfo
ResolveActionableMethod "dragSourceSetIconPixbuf" o = Gtk.Widget.WidgetDragSourceSetIconPixbufMethodInfo
ResolveActionableMethod "dragSourceSetIconStock" o = Gtk.Widget.WidgetDragSourceSetIconStockMethodInfo
ResolveActionableMethod "dragSourceSetTargetList" o = Gtk.Widget.WidgetDragSourceSetTargetListMethodInfo
ResolveActionableMethod "dragSourceUnset" o = Gtk.Widget.WidgetDragSourceUnsetMethodInfo
ResolveActionableMethod "dragUnhighlight" o = Gtk.Widget.WidgetDragUnhighlightMethodInfo
ResolveActionableMethod "draw" o = Gtk.Widget.WidgetDrawMethodInfo
ResolveActionableMethod "ensureStyle" o = Gtk.Widget.WidgetEnsureStyleMethodInfo
ResolveActionableMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
ResolveActionableMethod "event" o = Gtk.Widget.WidgetEventMethodInfo
ResolveActionableMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveActionableMethod "freezeChildNotify" o = Gtk.Widget.WidgetFreezeChildNotifyMethodInfo
ResolveActionableMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveActionableMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveActionableMethod "grabAdd" o = Gtk.Widget.WidgetGrabAddMethodInfo
ResolveActionableMethod "grabDefault" o = Gtk.Widget.WidgetGrabDefaultMethodInfo
ResolveActionableMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
ResolveActionableMethod "grabRemove" o = Gtk.Widget.WidgetGrabRemoveMethodInfo
ResolveActionableMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
ResolveActionableMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
ResolveActionableMethod "hasGrab" o = Gtk.Widget.WidgetHasGrabMethodInfo
ResolveActionableMethod "hasRcStyle" o = Gtk.Widget.WidgetHasRcStyleMethodInfo
ResolveActionableMethod "hasScreen" o = Gtk.Widget.WidgetHasScreenMethodInfo
ResolveActionableMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
ResolveActionableMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
ResolveActionableMethod "hideOnDelete" o = Gtk.Widget.WidgetHideOnDeleteMethodInfo
ResolveActionableMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
ResolveActionableMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
ResolveActionableMethod "inputShapeCombineRegion" o = Gtk.Widget.WidgetInputShapeCombineRegionMethodInfo
ResolveActionableMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
ResolveActionableMethod "intersect" o = Gtk.Widget.WidgetIntersectMethodInfo
ResolveActionableMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
ResolveActionableMethod "isComposited" o = Gtk.Widget.WidgetIsCompositedMethodInfo
ResolveActionableMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
ResolveActionableMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveActionableMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
ResolveActionableMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
ResolveActionableMethod "isToplevel" o = Gtk.Widget.WidgetIsToplevelMethodInfo
ResolveActionableMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
ResolveActionableMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
ResolveActionableMethod "listAccelClosures" o = Gtk.Widget.WidgetListAccelClosuresMethodInfo
ResolveActionableMethod "listActionPrefixes" o = Gtk.Widget.WidgetListActionPrefixesMethodInfo
ResolveActionableMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
ResolveActionableMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
ResolveActionableMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
ResolveActionableMethod "modifyBase" o = Gtk.Widget.WidgetModifyBaseMethodInfo
ResolveActionableMethod "modifyBg" o = Gtk.Widget.WidgetModifyBgMethodInfo
ResolveActionableMethod "modifyCursor" o = Gtk.Widget.WidgetModifyCursorMethodInfo
ResolveActionableMethod "modifyFg" o = Gtk.Widget.WidgetModifyFgMethodInfo
ResolveActionableMethod "modifyFont" o = Gtk.Widget.WidgetModifyFontMethodInfo
ResolveActionableMethod "modifyStyle" o = Gtk.Widget.WidgetModifyStyleMethodInfo
ResolveActionableMethod "modifyText" o = Gtk.Widget.WidgetModifyTextMethodInfo
ResolveActionableMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveActionableMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveActionableMethod "overrideBackgroundColor" o = Gtk.Widget.WidgetOverrideBackgroundColorMethodInfo
ResolveActionableMethod "overrideColor" o = Gtk.Widget.WidgetOverrideColorMethodInfo
ResolveActionableMethod "overrideCursor" o = Gtk.Widget.WidgetOverrideCursorMethodInfo
ResolveActionableMethod "overrideFont" o = Gtk.Widget.WidgetOverrideFontMethodInfo
ResolveActionableMethod "overrideSymbolicColor" o = Gtk.Widget.WidgetOverrideSymbolicColorMethodInfo
ResolveActionableMethod "parserFinished" o = Gtk.Buildable.BuildableParserFinishedMethodInfo
ResolveActionableMethod "path" o = Gtk.Widget.WidgetPathMethodInfo
ResolveActionableMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
ResolveActionableMethod "queueComputeExpand" o = Gtk.Widget.WidgetQueueComputeExpandMethodInfo
ResolveActionableMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
ResolveActionableMethod "queueDrawArea" o = Gtk.Widget.WidgetQueueDrawAreaMethodInfo
ResolveActionableMethod "queueDrawRegion" o = Gtk.Widget.WidgetQueueDrawRegionMethodInfo
ResolveActionableMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
ResolveActionableMethod "queueResizeNoRedraw" o = Gtk.Widget.WidgetQueueResizeNoRedrawMethodInfo
ResolveActionableMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
ResolveActionableMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveActionableMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveActionableMethod "regionIntersect" o = Gtk.Widget.WidgetRegionIntersectMethodInfo
ResolveActionableMethod "registerWindow" o = Gtk.Widget.WidgetRegisterWindowMethodInfo
ResolveActionableMethod "removeAccelerator" o = Gtk.Widget.WidgetRemoveAcceleratorMethodInfo
ResolveActionableMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
ResolveActionableMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
ResolveActionableMethod "renderIcon" o = Gtk.Widget.WidgetRenderIconMethodInfo
ResolveActionableMethod "renderIconPixbuf" o = Gtk.Widget.WidgetRenderIconPixbufMethodInfo
ResolveActionableMethod "reparent" o = Gtk.Widget.WidgetReparentMethodInfo
ResolveActionableMethod "resetRcStyles" o = Gtk.Widget.WidgetResetRcStylesMethodInfo
ResolveActionableMethod "resetStyle" o = Gtk.Widget.WidgetResetStyleMethodInfo
ResolveActionableMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveActionableMethod "sendExpose" o = Gtk.Widget.WidgetSendExposeMethodInfo
ResolveActionableMethod "sendFocusChange" o = Gtk.Widget.WidgetSendFocusChangeMethodInfo
ResolveActionableMethod "shapeCombineRegion" o = Gtk.Widget.WidgetShapeCombineRegionMethodInfo
ResolveActionableMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
ResolveActionableMethod "showAll" o = Gtk.Widget.WidgetShowAllMethodInfo
ResolveActionableMethod "showNow" o = Gtk.Widget.WidgetShowNowMethodInfo
ResolveActionableMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
ResolveActionableMethod "sizeAllocateWithBaseline" o = Gtk.Widget.WidgetSizeAllocateWithBaselineMethodInfo
ResolveActionableMethod "sizeRequest" o = Gtk.Widget.WidgetSizeRequestMethodInfo
ResolveActionableMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveActionableMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveActionableMethod "styleAttach" o = Gtk.Widget.WidgetStyleAttachMethodInfo
ResolveActionableMethod "styleGetProperty" o = Gtk.Widget.WidgetStyleGetPropertyMethodInfo
ResolveActionableMethod "thawChildNotify" o = Gtk.Widget.WidgetThawChildNotifyMethodInfo
ResolveActionableMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveActionableMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
ResolveActionableMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
ResolveActionableMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
ResolveActionableMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
ResolveActionableMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
ResolveActionableMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveActionableMethod "unregisterWindow" o = Gtk.Widget.WidgetUnregisterWindowMethodInfo
ResolveActionableMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
ResolveActionableMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveActionableMethod "getAccessible" o = Gtk.Widget.WidgetGetAccessibleMethodInfo
ResolveActionableMethod "getActionGroup" o = Gtk.Widget.WidgetGetActionGroupMethodInfo
ResolveActionableMethod "getActionName" o = ActionableGetActionNameMethodInfo
ResolveActionableMethod "getActionTargetValue" o = ActionableGetActionTargetValueMethodInfo
ResolveActionableMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
ResolveActionableMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
ResolveActionableMethod "getAllocatedSize" o = Gtk.Widget.WidgetGetAllocatedSizeMethodInfo
ResolveActionableMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
ResolveActionableMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
ResolveActionableMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
ResolveActionableMethod "getAppPaintable" o = Gtk.Widget.WidgetGetAppPaintableMethodInfo
ResolveActionableMethod "getCanDefault" o = Gtk.Widget.WidgetGetCanDefaultMethodInfo
ResolveActionableMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
ResolveActionableMethod "getChildRequisition" o = Gtk.Widget.WidgetGetChildRequisitionMethodInfo
ResolveActionableMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
ResolveActionableMethod "getClip" o = Gtk.Widget.WidgetGetClipMethodInfo
ResolveActionableMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
ResolveActionableMethod "getCompositeName" o = Gtk.Widget.WidgetGetCompositeNameMethodInfo
ResolveActionableMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveActionableMethod "getDeviceEnabled" o = Gtk.Widget.WidgetGetDeviceEnabledMethodInfo
ResolveActionableMethod "getDeviceEvents" o = Gtk.Widget.WidgetGetDeviceEventsMethodInfo
ResolveActionableMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
ResolveActionableMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
ResolveActionableMethod "getDoubleBuffered" o = Gtk.Widget.WidgetGetDoubleBufferedMethodInfo
ResolveActionableMethod "getEvents" o = Gtk.Widget.WidgetGetEventsMethodInfo
ResolveActionableMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
ResolveActionableMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
ResolveActionableMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
ResolveActionableMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
ResolveActionableMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
ResolveActionableMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
ResolveActionableMethod "getHasWindow" o = Gtk.Widget.WidgetGetHasWindowMethodInfo
ResolveActionableMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
ResolveActionableMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
ResolveActionableMethod "getInternalChild" o = Gtk.Buildable.BuildableGetInternalChildMethodInfo
ResolveActionableMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
ResolveActionableMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
ResolveActionableMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
ResolveActionableMethod "getMarginLeft" o = Gtk.Widget.WidgetGetMarginLeftMethodInfo
ResolveActionableMethod "getMarginRight" o = Gtk.Widget.WidgetGetMarginRightMethodInfo
ResolveActionableMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
ResolveActionableMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
ResolveActionableMethod "getModifierMask" o = Gtk.Widget.WidgetGetModifierMaskMethodInfo
ResolveActionableMethod "getModifierStyle" o = Gtk.Widget.WidgetGetModifierStyleMethodInfo
ResolveActionableMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
ResolveActionableMethod "getNoShowAll" o = Gtk.Widget.WidgetGetNoShowAllMethodInfo
ResolveActionableMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
ResolveActionableMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
ResolveActionableMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
ResolveActionableMethod "getParentWindow" o = Gtk.Widget.WidgetGetParentWindowMethodInfo
ResolveActionableMethod "getPath" o = Gtk.Widget.WidgetGetPathMethodInfo
ResolveActionableMethod "getPointer" o = Gtk.Widget.WidgetGetPointerMethodInfo
ResolveActionableMethod "getPreferredHeight" o = Gtk.Widget.WidgetGetPreferredHeightMethodInfo
ResolveActionableMethod "getPreferredHeightAndBaselineForWidth" o = Gtk.Widget.WidgetGetPreferredHeightAndBaselineForWidthMethodInfo
ResolveActionableMethod "getPreferredHeightForWidth" o = Gtk.Widget.WidgetGetPreferredHeightForWidthMethodInfo
ResolveActionableMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
ResolveActionableMethod "getPreferredWidth" o = Gtk.Widget.WidgetGetPreferredWidthMethodInfo
ResolveActionableMethod "getPreferredWidthForHeight" o = Gtk.Widget.WidgetGetPreferredWidthForHeightMethodInfo
ResolveActionableMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveActionableMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveActionableMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
ResolveActionableMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
ResolveActionableMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
ResolveActionableMethod "getRequisition" o = Gtk.Widget.WidgetGetRequisitionMethodInfo
ResolveActionableMethod "getRootWindow" o = Gtk.Widget.WidgetGetRootWindowMethodInfo
ResolveActionableMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
ResolveActionableMethod "getScreen" o = Gtk.Widget.WidgetGetScreenMethodInfo
ResolveActionableMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
ResolveActionableMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
ResolveActionableMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
ResolveActionableMethod "getState" o = Gtk.Widget.WidgetGetStateMethodInfo
ResolveActionableMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
ResolveActionableMethod "getStyle" o = Gtk.Widget.WidgetGetStyleMethodInfo
ResolveActionableMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
ResolveActionableMethod "getSupportMultidevice" o = Gtk.Widget.WidgetGetSupportMultideviceMethodInfo
ResolveActionableMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
ResolveActionableMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
ResolveActionableMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
ResolveActionableMethod "getTooltipWindow" o = Gtk.Widget.WidgetGetTooltipWindowMethodInfo
ResolveActionableMethod "getToplevel" o = Gtk.Widget.WidgetGetToplevelMethodInfo
ResolveActionableMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
ResolveActionableMethod "getValignWithBaseline" o = Gtk.Widget.WidgetGetValignWithBaselineMethodInfo
ResolveActionableMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
ResolveActionableMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
ResolveActionableMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
ResolveActionableMethod "getVisual" o = Gtk.Widget.WidgetGetVisualMethodInfo
ResolveActionableMethod "getWindow" o = Gtk.Widget.WidgetGetWindowMethodInfo
ResolveActionableMethod "setAccelPath" o = Gtk.Widget.WidgetSetAccelPathMethodInfo
ResolveActionableMethod "setActionName" o = ActionableSetActionNameMethodInfo
ResolveActionableMethod "setActionTargetValue" o = ActionableSetActionTargetValueMethodInfo
ResolveActionableMethod "setAllocation" o = Gtk.Widget.WidgetSetAllocationMethodInfo
ResolveActionableMethod "setAppPaintable" o = Gtk.Widget.WidgetSetAppPaintableMethodInfo
ResolveActionableMethod "setBuildableProperty" o = Gtk.Buildable.BuildableSetBuildablePropertyMethodInfo
ResolveActionableMethod "setCanDefault" o = Gtk.Widget.WidgetSetCanDefaultMethodInfo
ResolveActionableMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
ResolveActionableMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
ResolveActionableMethod "setClip" o = Gtk.Widget.WidgetSetClipMethodInfo
ResolveActionableMethod "setCompositeName" o = Gtk.Widget.WidgetSetCompositeNameMethodInfo
ResolveActionableMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveActionableMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveActionableMethod "setDetailedActionName" o = ActionableSetDetailedActionNameMethodInfo
ResolveActionableMethod "setDeviceEnabled" o = Gtk.Widget.WidgetSetDeviceEnabledMethodInfo
ResolveActionableMethod "setDeviceEvents" o = Gtk.Widget.WidgetSetDeviceEventsMethodInfo
ResolveActionableMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
ResolveActionableMethod "setDoubleBuffered" o = Gtk.Widget.WidgetSetDoubleBufferedMethodInfo
ResolveActionableMethod "setEvents" o = Gtk.Widget.WidgetSetEventsMethodInfo
ResolveActionableMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
ResolveActionableMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
ResolveActionableMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
ResolveActionableMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
ResolveActionableMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
ResolveActionableMethod "setHasWindow" o = Gtk.Widget.WidgetSetHasWindowMethodInfo
ResolveActionableMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
ResolveActionableMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
ResolveActionableMethod "setMapped" o = Gtk.Widget.WidgetSetMappedMethodInfo
ResolveActionableMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
ResolveActionableMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
ResolveActionableMethod "setMarginLeft" o = Gtk.Widget.WidgetSetMarginLeftMethodInfo
ResolveActionableMethod "setMarginRight" o = Gtk.Widget.WidgetSetMarginRightMethodInfo
ResolveActionableMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
ResolveActionableMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
ResolveActionableMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
ResolveActionableMethod "setNoShowAll" o = Gtk.Widget.WidgetSetNoShowAllMethodInfo
ResolveActionableMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
ResolveActionableMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
ResolveActionableMethod "setParentWindow" o = Gtk.Widget.WidgetSetParentWindowMethodInfo
ResolveActionableMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveActionableMethod "setRealized" o = Gtk.Widget.WidgetSetRealizedMethodInfo
ResolveActionableMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
ResolveActionableMethod "setRedrawOnAllocate" o = Gtk.Widget.WidgetSetRedrawOnAllocateMethodInfo
ResolveActionableMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
ResolveActionableMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
ResolveActionableMethod "setState" o = Gtk.Widget.WidgetSetStateMethodInfo
ResolveActionableMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
ResolveActionableMethod "setStyle" o = Gtk.Widget.WidgetSetStyleMethodInfo
ResolveActionableMethod "setSupportMultidevice" o = Gtk.Widget.WidgetSetSupportMultideviceMethodInfo
ResolveActionableMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
ResolveActionableMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
ResolveActionableMethod "setTooltipWindow" o = Gtk.Widget.WidgetSetTooltipWindowMethodInfo
ResolveActionableMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
ResolveActionableMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
ResolveActionableMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
ResolveActionableMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
ResolveActionableMethod "setVisual" o = Gtk.Widget.WidgetSetVisualMethodInfo
ResolveActionableMethod "setWindow" o = Gtk.Widget.WidgetSetWindowMethodInfo
ResolveActionableMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveActionableMethod t Actionable, O.MethodInfo info Actionable p) => OL.IsLabel t (Actionable -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
foreign import ccall "gtk_actionable_get_action_name" gtk_actionable_get_action_name ::
Ptr Actionable ->
IO CString
actionableGetActionName ::
(B.CallStack.HasCallStack, MonadIO m, IsActionable a) =>
a
-> m (Maybe T.Text)
actionableGetActionName :: a -> m (Maybe Text)
actionableGetActionName a
actionable = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
Ptr Actionable
actionable' <- a -> IO (Ptr Actionable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
actionable
CString
result <- Ptr Actionable -> IO CString
gtk_actionable_get_action_name Ptr Actionable
actionable'
Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
actionable
Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult
#if defined(ENABLE_OVERLOADING)
data ActionableGetActionNameMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsActionable a) => O.MethodInfo ActionableGetActionNameMethodInfo a signature where
overloadedMethod = actionableGetActionName
#endif
foreign import ccall "gtk_actionable_get_action_target_value" gtk_actionable_get_action_target_value ::
Ptr Actionable ->
IO (Ptr GVariant)
actionableGetActionTargetValue ::
(B.CallStack.HasCallStack, MonadIO m, IsActionable a) =>
a
-> m GVariant
actionableGetActionTargetValue :: a -> m GVariant
actionableGetActionTargetValue a
actionable = IO GVariant -> m GVariant
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GVariant -> m GVariant) -> IO GVariant -> m GVariant
forall a b. (a -> b) -> a -> b
$ do
Ptr Actionable
actionable' <- a -> IO (Ptr Actionable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
actionable
Ptr GVariant
result <- Ptr Actionable -> IO (Ptr GVariant)
gtk_actionable_get_action_target_value Ptr Actionable
actionable'
Text -> Ptr GVariant -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"actionableGetActionTargetValue" Ptr GVariant
result
GVariant
result' <- Ptr GVariant -> IO GVariant
B.GVariant.newGVariantFromPtr Ptr GVariant
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
actionable
GVariant -> IO GVariant
forall (m :: * -> *) a. Monad m => a -> m a
return GVariant
result'
#if defined(ENABLE_OVERLOADING)
data ActionableGetActionTargetValueMethodInfo
instance (signature ~ (m GVariant), MonadIO m, IsActionable a) => O.MethodInfo ActionableGetActionTargetValueMethodInfo a signature where
overloadedMethod = actionableGetActionTargetValue
#endif
foreign import ccall "gtk_actionable_set_action_name" gtk_actionable_set_action_name ::
Ptr Actionable ->
CString ->
IO ()
actionableSetActionName ::
(B.CallStack.HasCallStack, MonadIO m, IsActionable a) =>
a
-> Maybe (T.Text)
-> m ()
actionableSetActionName :: a -> Maybe Text -> m ()
actionableSetActionName a
actionable Maybe Text
actionName = 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 Actionable
actionable' <- a -> IO (Ptr Actionable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
actionable
CString
maybeActionName <- case Maybe Text
actionName of
Maybe Text
Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
Just Text
jActionName -> do
CString
jActionName' <- Text -> IO CString
textToCString Text
jActionName
CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jActionName'
Ptr Actionable -> CString -> IO ()
gtk_actionable_set_action_name Ptr Actionable
actionable' CString
maybeActionName
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
actionable
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeActionName
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ActionableSetActionNameMethodInfo
instance (signature ~ (Maybe (T.Text) -> m ()), MonadIO m, IsActionable a) => O.MethodInfo ActionableSetActionNameMethodInfo a signature where
overloadedMethod = actionableSetActionName
#endif
foreign import ccall "gtk_actionable_set_action_target_value" gtk_actionable_set_action_target_value ::
Ptr Actionable ->
Ptr GVariant ->
IO ()
actionableSetActionTargetValue ::
(B.CallStack.HasCallStack, MonadIO m, IsActionable a) =>
a
-> Maybe (GVariant)
-> m ()
actionableSetActionTargetValue :: a -> Maybe GVariant -> m ()
actionableSetActionTargetValue a
actionable Maybe GVariant
targetValue = 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 Actionable
actionable' <- a -> IO (Ptr Actionable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
actionable
Ptr GVariant
maybeTargetValue <- case Maybe GVariant
targetValue of
Maybe GVariant
Nothing -> Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
forall a. Ptr a
nullPtr
Just GVariant
jTargetValue -> do
Ptr GVariant
jTargetValue' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
jTargetValue
Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
jTargetValue'
Ptr Actionable -> Ptr GVariant -> IO ()
gtk_actionable_set_action_target_value Ptr Actionable
actionable' Ptr GVariant
maybeTargetValue
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
actionable
Maybe GVariant -> (GVariant -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe GVariant
targetValue GVariant -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ActionableSetActionTargetValueMethodInfo
instance (signature ~ (Maybe (GVariant) -> m ()), MonadIO m, IsActionable a) => O.MethodInfo ActionableSetActionTargetValueMethodInfo a signature where
overloadedMethod = actionableSetActionTargetValue
#endif
foreign import ccall "gtk_actionable_set_detailed_action_name" gtk_actionable_set_detailed_action_name ::
Ptr Actionable ->
CString ->
IO ()
actionableSetDetailedActionName ::
(B.CallStack.HasCallStack, MonadIO m, IsActionable a) =>
a
-> T.Text
-> m ()
actionableSetDetailedActionName :: a -> Text -> m ()
actionableSetDetailedActionName a
actionable Text
detailedActionName = 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 Actionable
actionable' <- a -> IO (Ptr Actionable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
actionable
CString
detailedActionName' <- Text -> IO CString
textToCString Text
detailedActionName
Ptr Actionable -> CString -> IO ()
gtk_actionable_set_detailed_action_name Ptr Actionable
actionable' CString
detailedActionName'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
actionable
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
detailedActionName'
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ActionableSetDetailedActionNameMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsActionable a) => O.MethodInfo ActionableSetDetailedActionNameMethodInfo a signature where
overloadedMethod = actionableSetDetailedActionName
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Actionable = ActionableSignalList
type ActionableSignalList = ('[ '("accelClosuresChanged", Gtk.Widget.WidgetAccelClosuresChangedSignalInfo), '("buttonPressEvent", Gtk.Widget.WidgetButtonPressEventSignalInfo), '("buttonReleaseEvent", Gtk.Widget.WidgetButtonReleaseEventSignalInfo), '("canActivateAccel", Gtk.Widget.WidgetCanActivateAccelSignalInfo), '("childNotify", Gtk.Widget.WidgetChildNotifySignalInfo), '("compositedChanged", Gtk.Widget.WidgetCompositedChangedSignalInfo), '("configureEvent", Gtk.Widget.WidgetConfigureEventSignalInfo), '("damageEvent", Gtk.Widget.WidgetDamageEventSignalInfo), '("deleteEvent", Gtk.Widget.WidgetDeleteEventSignalInfo), '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("destroyEvent", Gtk.Widget.WidgetDestroyEventSignalInfo), '("directionChanged", Gtk.Widget.WidgetDirectionChangedSignalInfo), '("dragBegin", Gtk.Widget.WidgetDragBeginSignalInfo), '("dragDataDelete", Gtk.Widget.WidgetDragDataDeleteSignalInfo), '("dragDataGet", Gtk.Widget.WidgetDragDataGetSignalInfo), '("dragDataReceived", Gtk.Widget.WidgetDragDataReceivedSignalInfo), '("dragDrop", Gtk.Widget.WidgetDragDropSignalInfo), '("dragEnd", Gtk.Widget.WidgetDragEndSignalInfo), '("dragFailed", Gtk.Widget.WidgetDragFailedSignalInfo), '("dragLeave", Gtk.Widget.WidgetDragLeaveSignalInfo), '("dragMotion", Gtk.Widget.WidgetDragMotionSignalInfo), '("draw", Gtk.Widget.WidgetDrawSignalInfo), '("enterNotifyEvent", Gtk.Widget.WidgetEnterNotifyEventSignalInfo), '("event", Gtk.Widget.WidgetEventSignalInfo), '("eventAfter", Gtk.Widget.WidgetEventAfterSignalInfo), '("focus", Gtk.Widget.WidgetFocusSignalInfo), '("focusInEvent", Gtk.Widget.WidgetFocusInEventSignalInfo), '("focusOutEvent", Gtk.Widget.WidgetFocusOutEventSignalInfo), '("grabBrokenEvent", Gtk.Widget.WidgetGrabBrokenEventSignalInfo), '("grabFocus", Gtk.Widget.WidgetGrabFocusSignalInfo), '("grabNotify", Gtk.Widget.WidgetGrabNotifySignalInfo), '("hide", Gtk.Widget.WidgetHideSignalInfo), '("hierarchyChanged", Gtk.Widget.WidgetHierarchyChangedSignalInfo), '("keyPressEvent", Gtk.Widget.WidgetKeyPressEventSignalInfo), '("keyReleaseEvent", Gtk.Widget.WidgetKeyReleaseEventSignalInfo), '("keynavFailed", Gtk.Widget.WidgetKeynavFailedSignalInfo), '("leaveNotifyEvent", Gtk.Widget.WidgetLeaveNotifyEventSignalInfo), '("map", Gtk.Widget.WidgetMapSignalInfo), '("mapEvent", Gtk.Widget.WidgetMapEventSignalInfo), '("mnemonicActivate", Gtk.Widget.WidgetMnemonicActivateSignalInfo), '("motionNotifyEvent", Gtk.Widget.WidgetMotionNotifyEventSignalInfo), '("moveFocus", Gtk.Widget.WidgetMoveFocusSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("parentSet", Gtk.Widget.WidgetParentSetSignalInfo), '("popupMenu", Gtk.Widget.WidgetPopupMenuSignalInfo), '("propertyNotifyEvent", Gtk.Widget.WidgetPropertyNotifyEventSignalInfo), '("proximityInEvent", Gtk.Widget.WidgetProximityInEventSignalInfo), '("proximityOutEvent", Gtk.Widget.WidgetProximityOutEventSignalInfo), '("queryTooltip", Gtk.Widget.WidgetQueryTooltipSignalInfo), '("realize", Gtk.Widget.WidgetRealizeSignalInfo), '("screenChanged", Gtk.Widget.WidgetScreenChangedSignalInfo), '("scrollEvent", Gtk.Widget.WidgetScrollEventSignalInfo), '("selectionClearEvent", Gtk.Widget.WidgetSelectionClearEventSignalInfo), '("selectionGet", Gtk.Widget.WidgetSelectionGetSignalInfo), '("selectionNotifyEvent", Gtk.Widget.WidgetSelectionNotifyEventSignalInfo), '("selectionReceived", Gtk.Widget.WidgetSelectionReceivedSignalInfo), '("selectionRequestEvent", Gtk.Widget.WidgetSelectionRequestEventSignalInfo), '("show", Gtk.Widget.WidgetShowSignalInfo), '("showHelp", Gtk.Widget.WidgetShowHelpSignalInfo), '("sizeAllocate", Gtk.Widget.WidgetSizeAllocateSignalInfo), '("stateChanged", Gtk.Widget.WidgetStateChangedSignalInfo), '("stateFlagsChanged", Gtk.Widget.WidgetStateFlagsChangedSignalInfo), '("styleSet", Gtk.Widget.WidgetStyleSetSignalInfo), '("styleUpdated", Gtk.Widget.WidgetStyleUpdatedSignalInfo), '("touchEvent", Gtk.Widget.WidgetTouchEventSignalInfo), '("unmap", Gtk.Widget.WidgetUnmapSignalInfo), '("unmapEvent", Gtk.Widget.WidgetUnmapEventSignalInfo), '("unrealize", Gtk.Widget.WidgetUnrealizeSignalInfo), '("visibilityNotifyEvent", Gtk.Widget.WidgetVisibilityNotifyEventSignalInfo), '("windowStateEvent", Gtk.Widget.WidgetWindowStateEventSignalInfo)] :: [(Symbol, *)])
#endif