{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- This interface provides a convenient way of associating widgets with
-- actions on a t'GI.Gtk.Objects.ApplicationWindow.ApplicationWindow' or t'GI.Gtk.Objects.Application.Application'.
-- 
-- It primarily consists of two properties: t'GI.Gtk.Interfaces.Actionable.Actionable':@/action-name/@
-- and t'GI.Gtk.Interfaces.Actionable.Actionable':@/action-target/@. There are also some convenience APIs
-- for setting these properties.
-- 
-- The action will be looked up in action groups that are found among
-- the widgets ancestors. Most commonly, these will be the actions with
-- the “win.” or “app.” prefix that are associated with the t'GI.Gtk.Objects.ApplicationWindow.ApplicationWindow'
-- or t'GI.Gtk.Objects.Application.Application', but other action groups that are added with
-- 'GI.Gtk.Objects.Widget.widgetInsertActionGroup' will be consulted as well.

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

module GI.Gtk.Interfaces.Actionable
    ( 

-- * Exported types
    Actionable(..)                          ,
    noActionable                            ,
    IsActionable                            ,
    toActionable                            ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveActionableMethod                 ,
#endif


-- ** getActionName #method:getActionName#

#if defined(ENABLE_OVERLOADING)
    ActionableGetActionNameMethodInfo       ,
#endif
    actionableGetActionName                 ,


-- ** getActionTargetValue #method:getActionTargetValue#

#if defined(ENABLE_OVERLOADING)
    ActionableGetActionTargetValueMethodInfo,
#endif
    actionableGetActionTargetValue          ,


-- ** setActionName #method:setActionName#

#if defined(ENABLE_OVERLOADING)
    ActionableSetActionNameMethodInfo       ,
#endif
    actionableSetActionName                 ,


-- ** setActionTargetValue #method:setActionTargetValue#

#if defined(ENABLE_OVERLOADING)
    ActionableSetActionTargetValueMethodInfo,
#endif
    actionableSetActionTargetValue          ,


-- ** setDetailedActionName #method:setDetailedActionName#

#if defined(ENABLE_OVERLOADING)
    ActionableSetDetailedActionNameMethodInfo,
#endif
    actionableSetDetailedActionName         ,




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

#if defined(ENABLE_OVERLOADING)
    ActionableActionNamePropertyInfo        ,
#endif
#if defined(ENABLE_OVERLOADING)
    actionableActionName                    ,
#endif
    clearActionableActionName               ,
    constructActionableActionName           ,
    getActionableActionName                 ,
    setActionableActionName                 ,


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

#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.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL

import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget

-- interface Actionable 
-- | Memory-managed wrapper type.
newtype Actionable = Actionable (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)
-- | A convenience alias for `Nothing` :: `Maybe` `Actionable`.
noActionable :: Maybe Actionable
noActionable :: Maybe Actionable
noActionable = Maybe Actionable
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Actionable = ActionableSignalList
type ActionableSignalList = ('[ '("accelClosuresChanged", Gtk.Widget.WidgetAccelClosuresChangedSignalInfo), '("canActivateAccel", Gtk.Widget.WidgetCanActivateAccelSignalInfo), '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("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), '("grabNotify", Gtk.Widget.WidgetGrabNotifySignalInfo), '("hide", Gtk.Widget.WidgetHideSignalInfo), '("keynavFailed", Gtk.Widget.WidgetKeynavFailedSignalInfo), '("map", Gtk.Widget.WidgetMapSignalInfo), '("mnemonicActivate", Gtk.Widget.WidgetMnemonicActivateSignalInfo), '("moveFocus", Gtk.Widget.WidgetMoveFocusSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("popupMenu", Gtk.Widget.WidgetPopupMenuSignalInfo), '("queryTooltip", Gtk.Widget.WidgetQueryTooltipSignalInfo), '("realize", Gtk.Widget.WidgetRealizeSignalInfo), '("show", Gtk.Widget.WidgetShowSignalInfo), '("sizeAllocate", Gtk.Widget.WidgetSizeAllocateSignalInfo), '("stateFlagsChanged", Gtk.Widget.WidgetStateFlagsChangedSignalInfo), '("styleUpdated", Gtk.Widget.WidgetStyleUpdatedSignalInfo), '("unmap", Gtk.Widget.WidgetUnmapSignalInfo), '("unrealize", Gtk.Widget.WidgetUnrealizeSignalInfo)] :: [(Symbol, *)])

#endif

foreign import ccall "gtk_actionable_get_type"
    c_gtk_actionable_get_type :: IO GType

instance GObject Actionable where
    gobjectType :: IO GType
gobjectType = IO GType
c_gtk_actionable_get_type
    

-- | Convert 'Actionable' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue Actionable where
    toGValue :: Actionable -> IO GValue
toGValue o :: 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 gv :: 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
        
    

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

instance O.HasParentTypes Actionable
type instance O.ParentTypes Actionable = '[GObject.Object.Object, Gtk.Widget.Widget]

-- | Cast to `Actionable`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
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, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr Actionable -> Actionable
Actionable

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

-- | Get the value of the “@action-name@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' actionable #actionName
-- @
getActionableActionName :: (MonadIO m, IsActionable o) => o -> m (Maybe T.Text)
getActionableActionName :: o -> m (Maybe Text)
getActionableActionName obj :: o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj "action-name"

-- | Set the value of the “@action-name@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' actionable [ #actionName 'Data.GI.Base.Attributes.:=' value ]
-- @
setActionableActionName :: (MonadIO m, IsActionable o) => o -> T.Text -> m ()
setActionableActionName :: o -> Text -> m ()
setActionableActionName obj :: o
obj val :: Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj "action-name" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

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

-- | Set the value of the “@action-name@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #actionName
-- @
clearActionableActionName :: (MonadIO m, IsActionable o) => o -> m ()
clearActionableActionName :: o -> m ()
clearActionableActionName obj :: o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj "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

-- VVV Prop "action-target"
   -- Type: TVariant
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@action-target@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' actionable #actionTarget
-- @
getActionableActionTarget :: (MonadIO m, IsActionable o) => o -> m (Maybe GVariant)
getActionableActionTarget :: o -> m (Maybe GVariant)
getActionableActionTarget obj :: 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 "action-target"

-- | Set the value of the “@action-target@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' actionable [ #actionTarget 'Data.GI.Base.Attributes.:=' value ]
-- @
setActionableActionTarget :: (MonadIO m, IsActionable o) => o -> GVariant -> m ()
setActionableActionTarget :: o -> GVariant -> m ()
setActionableActionTarget obj :: o
obj val :: 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 "action-target" (GVariant -> Maybe GVariant
forall a. a -> Maybe a
Just GVariant
val)

-- | Construct a `GValueConstruct` with valid value for the “@action-target@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructActionableActionTarget :: (IsActionable o) => GVariant -> IO (GValueConstruct o)
constructActionableActionTarget :: GVariant -> IO (GValueConstruct o)
constructActionableActionTarget val :: GVariant
val = String -> Maybe GVariant -> IO (GValueConstruct o)
forall o. String -> Maybe GVariant -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyVariant "action-target" (GVariant -> Maybe GVariant
forall a. a -> Maybe a
Just GVariant
val)

-- | Set the value of the “@action-target@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #actionTarget
-- @
clearActionableActionTarget :: (MonadIO m, IsActionable o) => o -> m ()
clearActionableActionTarget :: o -> m ()
clearActionableActionTarget obj :: o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe GVariant -> IO ()
forall a. GObject a => a -> String -> Maybe GVariant -> IO ()
B.Properties.setObjectPropertyVariant o
obj "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), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("canTarget", Gtk.Widget.WidgetCanTargetPropertyInfo), '("cssName", Gtk.Widget.WidgetCssNamePropertyInfo), '("cursor", Gtk.Widget.WidgetCursorPropertyInfo), '("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), '("layoutManager", Gtk.Widget.WidgetLayoutManagerPropertyInfo), '("margin", Gtk.Widget.WidgetMarginPropertyInfo), '("marginBottom", Gtk.Widget.WidgetMarginBottomPropertyInfo), '("marginEnd", Gtk.Widget.WidgetMarginEndPropertyInfo), '("marginStart", Gtk.Widget.WidgetMarginStartPropertyInfo), '("marginTop", Gtk.Widget.WidgetMarginTopPropertyInfo), '("name", Gtk.Widget.WidgetNamePropertyInfo), '("opacity", Gtk.Widget.WidgetOpacityPropertyInfo), '("overflow", Gtk.Widget.WidgetOverflowPropertyInfo), '("parent", Gtk.Widget.WidgetParentPropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("root", Gtk.Widget.WidgetRootPropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("surface", Gtk.Widget.WidgetSurfacePropertyInfo), '("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)] :: [(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 "activateAction" o = Gtk.Widget.WidgetActivateActionMethodInfo
    ResolveActionableMethod "activateDefault" o = Gtk.Widget.WidgetActivateDefaultMethodInfo
    ResolveActionableMethod "addAccelerator" o = Gtk.Widget.WidgetAddAcceleratorMethodInfo
    ResolveActionableMethod "addChild" o = Gtk.Buildable.BuildableAddChildMethodInfo
    ResolveActionableMethod "addController" o = Gtk.Widget.WidgetAddControllerMethodInfo
    ResolveActionableMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
    ResolveActionableMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
    ResolveActionableMethod "allocate" o = Gtk.Widget.WidgetAllocateMethodInfo
    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 "computeBounds" o = Gtk.Widget.WidgetComputeBoundsMethodInfo
    ResolveActionableMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
    ResolveActionableMethod "computePoint" o = Gtk.Widget.WidgetComputePointMethodInfo
    ResolveActionableMethod "computeTransform" o = Gtk.Widget.WidgetComputeTransformMethodInfo
    ResolveActionableMethod "constructChild" o = Gtk.Buildable.BuildableConstructChildMethodInfo
    ResolveActionableMethod "contains" o = Gtk.Widget.WidgetContainsMethodInfo
    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 "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 "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 "dragSourceSetIconPaintable" o = Gtk.Widget.WidgetDragSourceSetIconPaintableMethodInfo
    ResolveActionableMethod "dragSourceSetTargetList" o = Gtk.Widget.WidgetDragSourceSetTargetListMethodInfo
    ResolveActionableMethod "dragSourceUnset" o = Gtk.Widget.WidgetDragSourceUnsetMethodInfo
    ResolveActionableMethod "dragUnhighlight" o = Gtk.Widget.WidgetDragUnhighlightMethodInfo
    ResolveActionableMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
    ResolveActionableMethod "event" o = Gtk.Widget.WidgetEventMethodInfo
    ResolveActionableMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveActionableMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveActionableMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveActionableMethod "grabAdd" o = Gtk.Widget.WidgetGrabAddMethodInfo
    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 "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
    ResolveActionableMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
    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 "insertAfter" o = Gtk.Widget.WidgetInsertAfterMethodInfo
    ResolveActionableMethod "insertBefore" o = Gtk.Widget.WidgetInsertBeforeMethodInfo
    ResolveActionableMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
    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 "measure" o = Gtk.Widget.WidgetMeasureMethodInfo
    ResolveActionableMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
    ResolveActionableMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveActionableMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveActionableMethod "observeChildren" o = Gtk.Widget.WidgetObserveChildrenMethodInfo
    ResolveActionableMethod "observeControllers" o = Gtk.Widget.WidgetObserveControllersMethodInfo
    ResolveActionableMethod "parserFinished" o = Gtk.Buildable.BuildableParserFinishedMethodInfo
    ResolveActionableMethod "pick" o = Gtk.Widget.WidgetPickMethodInfo
    ResolveActionableMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
    ResolveActionableMethod "queueComputeExpand" o = Gtk.Widget.WidgetQueueComputeExpandMethodInfo
    ResolveActionableMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
    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 "registerSurface" o = Gtk.Widget.WidgetRegisterSurfaceMethodInfo
    ResolveActionableMethod "removeAccelerator" o = Gtk.Widget.WidgetRemoveAcceleratorMethodInfo
    ResolveActionableMethod "removeController" o = Gtk.Widget.WidgetRemoveControllerMethodInfo
    ResolveActionableMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
    ResolveActionableMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
    ResolveActionableMethod "resetStyle" o = Gtk.Widget.WidgetResetStyleMethodInfo
    ResolveActionableMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveActionableMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
    ResolveActionableMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
    ResolveActionableMethod "snapshotChild" o = Gtk.Widget.WidgetSnapshotChildMethodInfo
    ResolveActionableMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveActionableMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    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 "unregisterSurface" o = Gtk.Widget.WidgetUnregisterSurfaceMethodInfo
    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 "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
    ResolveActionableMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
    ResolveActionableMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
    ResolveActionableMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
    ResolveActionableMethod "getCanTarget" o = Gtk.Widget.WidgetGetCanTargetMethodInfo
    ResolveActionableMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
    ResolveActionableMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
    ResolveActionableMethod "getCursor" o = Gtk.Widget.WidgetGetCursorMethodInfo
    ResolveActionableMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveActionableMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
    ResolveActionableMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
    ResolveActionableMethod "getFirstChild" o = Gtk.Widget.WidgetGetFirstChildMethodInfo
    ResolveActionableMethod "getFocusChild" o = Gtk.Widget.WidgetGetFocusChildMethodInfo
    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 "getHasSurface" o = Gtk.Widget.WidgetGetHasSurfaceMethodInfo
    ResolveActionableMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
    ResolveActionableMethod "getHeight" o = Gtk.Widget.WidgetGetHeightMethodInfo
    ResolveActionableMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
    ResolveActionableMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
    ResolveActionableMethod "getInternalChild" o = Gtk.Buildable.BuildableGetInternalChildMethodInfo
    ResolveActionableMethod "getLastChild" o = Gtk.Widget.WidgetGetLastChildMethodInfo
    ResolveActionableMethod "getLayoutManager" o = Gtk.Widget.WidgetGetLayoutManagerMethodInfo
    ResolveActionableMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
    ResolveActionableMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
    ResolveActionableMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
    ResolveActionableMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
    ResolveActionableMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
    ResolveActionableMethod "getModifierMask" o = Gtk.Widget.WidgetGetModifierMaskMethodInfo
    ResolveActionableMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
    ResolveActionableMethod "getNextSibling" o = Gtk.Widget.WidgetGetNextSiblingMethodInfo
    ResolveActionableMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
    ResolveActionableMethod "getOverflow" o = Gtk.Widget.WidgetGetOverflowMethodInfo
    ResolveActionableMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
    ResolveActionableMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
    ResolveActionableMethod "getPath" o = Gtk.Widget.WidgetGetPathMethodInfo
    ResolveActionableMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
    ResolveActionableMethod "getPrevSibling" o = Gtk.Widget.WidgetGetPrevSiblingMethodInfo
    ResolveActionableMethod "getPrimaryClipboard" o = Gtk.Widget.WidgetGetPrimaryClipboardMethodInfo
    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 "getRoot" o = Gtk.Widget.WidgetGetRootMethodInfo
    ResolveActionableMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
    ResolveActionableMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
    ResolveActionableMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
    ResolveActionableMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
    ResolveActionableMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
    ResolveActionableMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
    ResolveActionableMethod "getSupportMultidevice" o = Gtk.Widget.WidgetGetSupportMultideviceMethodInfo
    ResolveActionableMethod "getSurface" o = Gtk.Widget.WidgetGetSurfaceMethodInfo
    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 "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
    ResolveActionableMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
    ResolveActionableMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
    ResolveActionableMethod "getWidth" o = Gtk.Widget.WidgetGetWidthMethodInfo
    ResolveActionableMethod "setAccelPath" o = Gtk.Widget.WidgetSetAccelPathMethodInfo
    ResolveActionableMethod "setActionName" o = ActionableSetActionNameMethodInfo
    ResolveActionableMethod "setActionTargetValue" o = ActionableSetActionTargetValueMethodInfo
    ResolveActionableMethod "setBuildableProperty" o = Gtk.Buildable.BuildableSetBuildablePropertyMethodInfo
    ResolveActionableMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
    ResolveActionableMethod "setCanTarget" o = Gtk.Widget.WidgetSetCanTargetMethodInfo
    ResolveActionableMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
    ResolveActionableMethod "setCursor" o = Gtk.Widget.WidgetSetCursorMethodInfo
    ResolveActionableMethod "setCursorFromName" o = Gtk.Widget.WidgetSetCursorFromNameMethodInfo
    ResolveActionableMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveActionableMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveActionableMethod "setDetailedActionName" o = ActionableSetDetailedActionNameMethodInfo
    ResolveActionableMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
    ResolveActionableMethod "setFocusChild" o = Gtk.Widget.WidgetSetFocusChildMethodInfo
    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 "setHasSurface" o = Gtk.Widget.WidgetSetHasSurfaceMethodInfo
    ResolveActionableMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
    ResolveActionableMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
    ResolveActionableMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
    ResolveActionableMethod "setLayoutManager" o = Gtk.Widget.WidgetSetLayoutManagerMethodInfo
    ResolveActionableMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
    ResolveActionableMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
    ResolveActionableMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
    ResolveActionableMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
    ResolveActionableMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
    ResolveActionableMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
    ResolveActionableMethod "setOverflow" o = Gtk.Widget.WidgetSetOverflowMethodInfo
    ResolveActionableMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
    ResolveActionableMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveActionableMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
    ResolveActionableMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
    ResolveActionableMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
    ResolveActionableMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
    ResolveActionableMethod "setSupportMultidevice" o = Gtk.Widget.WidgetSetSupportMultideviceMethodInfo
    ResolveActionableMethod "setSurface" o = Gtk.Widget.WidgetSetSurfaceMethodInfo
    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 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

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

foreign import ccall "gtk_actionable_get_action_name" gtk_actionable_get_action_name :: 
    Ptr Actionable ->                       -- actionable : TInterface (Name {namespace = "Gtk", name = "Actionable"})
    IO CString

-- | Gets the action name for /@actionable@/.
-- 
-- See 'GI.Gtk.Interfaces.Actionable.actionableSetActionName' for more information.
actionableGetActionName ::
    (B.CallStack.HasCallStack, MonadIO m, IsActionable a) =>
    a
    -- ^ /@actionable@/: a t'GI.Gtk.Interfaces.Actionable.Actionable' widget
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the action name, or 'P.Nothing' if none is set
actionableGetActionName :: a -> m (Maybe Text)
actionableGetActionName actionable :: 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
$ \result' :: 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

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

foreign import ccall "gtk_actionable_get_action_target_value" gtk_actionable_get_action_target_value :: 
    Ptr Actionable ->                       -- actionable : TInterface (Name {namespace = "Gtk", name = "Actionable"})
    IO (Ptr GVariant)

-- | Gets the current target value of /@actionable@/.
-- 
-- See 'GI.Gtk.Interfaces.Actionable.actionableSetActionTargetValue' for more information.
actionableGetActionTargetValue ::
    (B.CallStack.HasCallStack, MonadIO m, IsActionable a) =>
    a
    -- ^ /@actionable@/: a t'GI.Gtk.Interfaces.Actionable.Actionable' widget
    -> m GVariant
    -- ^ __Returns:__ the current target value
actionableGetActionTargetValue :: a -> m GVariant
actionableGetActionTargetValue actionable :: 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 "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

-- method Actionable::set_action_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "actionable"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Actionable" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkActionable widget"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "action_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an action name, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_actionable_set_action_name" gtk_actionable_set_action_name :: 
    Ptr Actionable ->                       -- actionable : TInterface (Name {namespace = "Gtk", name = "Actionable"})
    CString ->                              -- action_name : TBasicType TUTF8
    IO ()

-- | Specifies the name of the action with which this widget should be
-- associated.  If /@actionName@/ is 'P.Nothing' then the widget will be
-- unassociated from any previous action.
-- 
-- Usually this function is used when the widget is located (or will be
-- located) within the hierarchy of a t'GI.Gtk.Objects.ApplicationWindow.ApplicationWindow'.
-- 
-- Names are of the form “win.save” or “app.quit” for actions on the
-- containing t'GI.Gtk.Objects.ApplicationWindow.ApplicationWindow' or its associated t'GI.Gtk.Objects.Application.Application',
-- respectively.  This is the same form used for actions in the t'GI.Gio.Objects.Menu.Menu'
-- associated with the window.
actionableSetActionName ::
    (B.CallStack.HasCallStack, MonadIO m, IsActionable a) =>
    a
    -- ^ /@actionable@/: a t'GI.Gtk.Interfaces.Actionable.Actionable' widget
    -> Maybe (T.Text)
    -- ^ /@actionName@/: an action name, or 'P.Nothing'
    -> m ()
actionableSetActionName :: a -> Maybe Text -> m ()
actionableSetActionName actionable :: a
actionable actionName :: 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
        Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just jActionName :: 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

-- method Actionable::set_action_target_value
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "actionable"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Actionable" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkActionable widget"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "target_value"
--           , argType = TVariant
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GVariant to set as the target value, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_actionable_set_action_target_value" gtk_actionable_set_action_target_value :: 
    Ptr Actionable ->                       -- actionable : TInterface (Name {namespace = "Gtk", name = "Actionable"})
    Ptr GVariant ->                         -- target_value : TVariant
    IO ()

-- | Sets the target value of an actionable widget.
-- 
-- If /@targetValue@/ is 'P.Nothing' then the target value is unset.
-- 
-- The target value has two purposes.  First, it is used as the
-- parameter to activation of the action associated with the
-- t'GI.Gtk.Interfaces.Actionable.Actionable' widget. Second, it is used to determine if the widget
-- should be rendered as “active” — the widget is active if the state
-- is equal to the given target.
-- 
-- Consider the example of associating a set of buttons with a t'GI.Gio.Interfaces.Action.Action'
-- with string state in a typical “radio button” situation.  Each button
-- will be associated with the same action, but with a different target
-- value for that action.  Clicking on a particular button will activate
-- the action with the target of that button, which will typically cause
-- the action’s state to change to that value. Since the action’s state
-- is now equal to the target value of the button, the button will now
-- be rendered as active (and the other buttons, with different targets,
-- rendered inactive).
actionableSetActionTargetValue ::
    (B.CallStack.HasCallStack, MonadIO m, IsActionable a) =>
    a
    -- ^ /@actionable@/: a t'GI.Gtk.Interfaces.Actionable.Actionable' widget
    -> Maybe (GVariant)
    -- ^ /@targetValue@/: a t'GVariant' to set as the target value, or 'P.Nothing'
    -> m ()
actionableSetActionTargetValue :: a -> Maybe GVariant -> m ()
actionableSetActionTargetValue actionable :: a
actionable targetValue :: 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
        Nothing -> Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
forall a. Ptr a
nullPtr
        Just jTargetValue :: 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

-- method Actionable::set_detailed_action_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "actionable"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Actionable" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkActionable widget"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "detailed_action_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the detailed action name"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_actionable_set_detailed_action_name" gtk_actionable_set_detailed_action_name :: 
    Ptr Actionable ->                       -- actionable : TInterface (Name {namespace = "Gtk", name = "Actionable"})
    CString ->                              -- detailed_action_name : TBasicType TUTF8
    IO ()

-- | Sets the action-name and associated string target value of an
-- actionable widget.
-- 
-- /@detailedActionName@/ is a string in the format accepted by
-- 'GI.Gio.Functions.actionParseDetailedName'.
-- 
-- (Note that prior to version 3.22.25,
-- this function is only usable for actions with a simple \"s\" target, and
-- /@detailedActionName@/ must be of the form @\"action::target\"@ where
-- @action@ is the action name and @target@ is the string to use
-- as the target.)
actionableSetDetailedActionName ::
    (B.CallStack.HasCallStack, MonadIO m, IsActionable a) =>
    a
    -- ^ /@actionable@/: a t'GI.Gtk.Interfaces.Actionable.Actionable' widget
    -> T.Text
    -- ^ /@detailedActionName@/: the detailed action name
    -> m ()
actionableSetDetailedActionName :: a -> Text -> m ()
actionableSetDetailedActionName actionable :: a
actionable detailedActionName :: 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