{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The @GtkActionable@ interface provides a convenient way of asscociating
-- widgets with actions.
-- 
-- 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
-- @GtkApplicationWindow@ or @GtkApplication@, 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(..)                          ,
    IsActionable                            ,
    toActionable                            ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [actionSetEnabled]("GI.Gtk.Objects.Widget#g:method:actionSetEnabled"), [activate]("GI.Gtk.Objects.Widget#g:method:activate"), [activateAction]("GI.Gtk.Objects.Widget#g:method:activateAction"), [activateDefault]("GI.Gtk.Objects.Widget#g:method:activateDefault"), [addController]("GI.Gtk.Objects.Widget#g:method:addController"), [addCssClass]("GI.Gtk.Objects.Widget#g:method:addCssClass"), [addMnemonicLabel]("GI.Gtk.Objects.Widget#g:method:addMnemonicLabel"), [addTickCallback]("GI.Gtk.Objects.Widget#g:method:addTickCallback"), [allocate]("GI.Gtk.Objects.Widget#g:method:allocate"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [childFocus]("GI.Gtk.Objects.Widget#g:method:childFocus"), [computeBounds]("GI.Gtk.Objects.Widget#g:method:computeBounds"), [computeExpand]("GI.Gtk.Objects.Widget#g:method:computeExpand"), [computePoint]("GI.Gtk.Objects.Widget#g:method:computePoint"), [computeTransform]("GI.Gtk.Objects.Widget#g:method:computeTransform"), [contains]("GI.Gtk.Objects.Widget#g:method:contains"), [createPangoContext]("GI.Gtk.Objects.Widget#g:method:createPangoContext"), [createPangoLayout]("GI.Gtk.Objects.Widget#g:method:createPangoLayout"), [dragCheckThreshold]("GI.Gtk.Objects.Widget#g:method:dragCheckThreshold"), [errorBell]("GI.Gtk.Objects.Widget#g:method:errorBell"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [grabFocus]("GI.Gtk.Objects.Widget#g:method:grabFocus"), [hasCssClass]("GI.Gtk.Objects.Widget#g:method:hasCssClass"), [hasDefault]("GI.Gtk.Objects.Widget#g:method:hasDefault"), [hasFocus]("GI.Gtk.Objects.Widget#g:method:hasFocus"), [hasVisibleFocus]("GI.Gtk.Objects.Widget#g:method:hasVisibleFocus"), [hide]("GI.Gtk.Objects.Widget#g:method:hide"), [inDestruction]("GI.Gtk.Objects.Widget#g:method:inDestruction"), [initTemplate]("GI.Gtk.Objects.Widget#g:method:initTemplate"), [insertActionGroup]("GI.Gtk.Objects.Widget#g:method:insertActionGroup"), [insertAfter]("GI.Gtk.Objects.Widget#g:method:insertAfter"), [insertBefore]("GI.Gtk.Objects.Widget#g:method:insertBefore"), [isAncestor]("GI.Gtk.Objects.Widget#g:method:isAncestor"), [isDrawable]("GI.Gtk.Objects.Widget#g:method:isDrawable"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [isFocus]("GI.Gtk.Objects.Widget#g:method:isFocus"), [isSensitive]("GI.Gtk.Objects.Widget#g:method:isSensitive"), [isVisible]("GI.Gtk.Objects.Widget#g:method:isVisible"), [keynavFailed]("GI.Gtk.Objects.Widget#g:method:keynavFailed"), [listMnemonicLabels]("GI.Gtk.Objects.Widget#g:method:listMnemonicLabels"), [map]("GI.Gtk.Objects.Widget#g:method:map"), [measure]("GI.Gtk.Objects.Widget#g:method:measure"), [mnemonicActivate]("GI.Gtk.Objects.Widget#g:method:mnemonicActivate"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [observeChildren]("GI.Gtk.Objects.Widget#g:method:observeChildren"), [observeControllers]("GI.Gtk.Objects.Widget#g:method:observeControllers"), [pick]("GI.Gtk.Objects.Widget#g:method:pick"), [queueAllocate]("GI.Gtk.Objects.Widget#g:method:queueAllocate"), [queueDraw]("GI.Gtk.Objects.Widget#g:method:queueDraw"), [queueResize]("GI.Gtk.Objects.Widget#g:method:queueResize"), [realize]("GI.Gtk.Objects.Widget#g:method:realize"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [removeController]("GI.Gtk.Objects.Widget#g:method:removeController"), [removeCssClass]("GI.Gtk.Objects.Widget#g:method:removeCssClass"), [removeMnemonicLabel]("GI.Gtk.Objects.Widget#g:method:removeMnemonicLabel"), [removeTickCallback]("GI.Gtk.Objects.Widget#g:method:removeTickCallback"), [resetProperty]("GI.Gtk.Interfaces.Accessible#g:method:resetProperty"), [resetRelation]("GI.Gtk.Interfaces.Accessible#g:method:resetRelation"), [resetState]("GI.Gtk.Interfaces.Accessible#g:method:resetState"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [shouldLayout]("GI.Gtk.Objects.Widget#g:method:shouldLayout"), [show]("GI.Gtk.Objects.Widget#g:method:show"), [sizeAllocate]("GI.Gtk.Objects.Widget#g:method:sizeAllocate"), [snapshotChild]("GI.Gtk.Objects.Widget#g:method:snapshotChild"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [translateCoordinates]("GI.Gtk.Objects.Widget#g:method:translateCoordinates"), [triggerTooltipQuery]("GI.Gtk.Objects.Widget#g:method:triggerTooltipQuery"), [unmap]("GI.Gtk.Objects.Widget#g:method:unmap"), [unparent]("GI.Gtk.Objects.Widget#g:method:unparent"), [unrealize]("GI.Gtk.Objects.Widget#g:method:unrealize"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [unsetStateFlags]("GI.Gtk.Objects.Widget#g:method:unsetStateFlags"), [updateProperty]("GI.Gtk.Interfaces.Accessible#g:method:updateProperty"), [updateRelation]("GI.Gtk.Interfaces.Accessible#g:method:updateRelation"), [updateState]("GI.Gtk.Interfaces.Accessible#g:method:updateState"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAccessibleRole]("GI.Gtk.Interfaces.Accessible#g:method:getAccessibleRole"), [getActionName]("GI.Gtk.Interfaces.Actionable#g:method:getActionName"), [getActionTargetValue]("GI.Gtk.Interfaces.Actionable#g:method:getActionTargetValue"), [getAllocatedBaseline]("GI.Gtk.Objects.Widget#g:method:getAllocatedBaseline"), [getAllocatedHeight]("GI.Gtk.Objects.Widget#g:method:getAllocatedHeight"), [getAllocatedWidth]("GI.Gtk.Objects.Widget#g:method:getAllocatedWidth"), [getAllocation]("GI.Gtk.Objects.Widget#g:method:getAllocation"), [getAncestor]("GI.Gtk.Objects.Widget#g:method:getAncestor"), [getBuildableId]("GI.Gtk.Interfaces.Buildable#g:method:getBuildableId"), [getCanFocus]("GI.Gtk.Objects.Widget#g:method:getCanFocus"), [getCanTarget]("GI.Gtk.Objects.Widget#g:method:getCanTarget"), [getChildVisible]("GI.Gtk.Objects.Widget#g:method:getChildVisible"), [getClipboard]("GI.Gtk.Objects.Widget#g:method:getClipboard"), [getCssClasses]("GI.Gtk.Objects.Widget#g:method:getCssClasses"), [getCssName]("GI.Gtk.Objects.Widget#g:method:getCssName"), [getCursor]("GI.Gtk.Objects.Widget#g:method:getCursor"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDirection]("GI.Gtk.Objects.Widget#g:method:getDirection"), [getDisplay]("GI.Gtk.Objects.Widget#g:method:getDisplay"), [getFirstChild]("GI.Gtk.Objects.Widget#g:method:getFirstChild"), [getFocusChild]("GI.Gtk.Objects.Widget#g:method:getFocusChild"), [getFocusOnClick]("GI.Gtk.Objects.Widget#g:method:getFocusOnClick"), [getFocusable]("GI.Gtk.Objects.Widget#g:method:getFocusable"), [getFontMap]("GI.Gtk.Objects.Widget#g:method:getFontMap"), [getFontOptions]("GI.Gtk.Objects.Widget#g:method:getFontOptions"), [getFrameClock]("GI.Gtk.Objects.Widget#g:method:getFrameClock"), [getHalign]("GI.Gtk.Objects.Widget#g:method:getHalign"), [getHasTooltip]("GI.Gtk.Objects.Widget#g:method:getHasTooltip"), [getHeight]("GI.Gtk.Objects.Widget#g:method:getHeight"), [getHexpand]("GI.Gtk.Objects.Widget#g:method:getHexpand"), [getHexpandSet]("GI.Gtk.Objects.Widget#g:method:getHexpandSet"), [getLastChild]("GI.Gtk.Objects.Widget#g:method:getLastChild"), [getLayoutManager]("GI.Gtk.Objects.Widget#g:method:getLayoutManager"), [getMapped]("GI.Gtk.Objects.Widget#g:method:getMapped"), [getMarginBottom]("GI.Gtk.Objects.Widget#g:method:getMarginBottom"), [getMarginEnd]("GI.Gtk.Objects.Widget#g:method:getMarginEnd"), [getMarginStart]("GI.Gtk.Objects.Widget#g:method:getMarginStart"), [getMarginTop]("GI.Gtk.Objects.Widget#g:method:getMarginTop"), [getName]("GI.Gtk.Objects.Widget#g:method:getName"), [getNative]("GI.Gtk.Objects.Widget#g:method:getNative"), [getNextSibling]("GI.Gtk.Objects.Widget#g:method:getNextSibling"), [getOpacity]("GI.Gtk.Objects.Widget#g:method:getOpacity"), [getOverflow]("GI.Gtk.Objects.Widget#g:method:getOverflow"), [getPangoContext]("GI.Gtk.Objects.Widget#g:method:getPangoContext"), [getParent]("GI.Gtk.Objects.Widget#g:method:getParent"), [getPreferredSize]("GI.Gtk.Objects.Widget#g:method:getPreferredSize"), [getPrevSibling]("GI.Gtk.Objects.Widget#g:method:getPrevSibling"), [getPrimaryClipboard]("GI.Gtk.Objects.Widget#g:method:getPrimaryClipboard"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRealized]("GI.Gtk.Objects.Widget#g:method:getRealized"), [getReceivesDefault]("GI.Gtk.Objects.Widget#g:method:getReceivesDefault"), [getRequestMode]("GI.Gtk.Objects.Widget#g:method:getRequestMode"), [getRoot]("GI.Gtk.Objects.Widget#g:method:getRoot"), [getScaleFactor]("GI.Gtk.Objects.Widget#g:method:getScaleFactor"), [getSensitive]("GI.Gtk.Objects.Widget#g:method:getSensitive"), [getSettings]("GI.Gtk.Objects.Widget#g:method:getSettings"), [getSize]("GI.Gtk.Objects.Widget#g:method:getSize"), [getSizeRequest]("GI.Gtk.Objects.Widget#g:method:getSizeRequest"), [getStateFlags]("GI.Gtk.Objects.Widget#g:method:getStateFlags"), [getStyleContext]("GI.Gtk.Objects.Widget#g:method:getStyleContext"), [getTemplateChild]("GI.Gtk.Objects.Widget#g:method:getTemplateChild"), [getTooltipMarkup]("GI.Gtk.Objects.Widget#g:method:getTooltipMarkup"), [getTooltipText]("GI.Gtk.Objects.Widget#g:method:getTooltipText"), [getValign]("GI.Gtk.Objects.Widget#g:method:getValign"), [getVexpand]("GI.Gtk.Objects.Widget#g:method:getVexpand"), [getVexpandSet]("GI.Gtk.Objects.Widget#g:method:getVexpandSet"), [getVisible]("GI.Gtk.Objects.Widget#g:method:getVisible"), [getWidth]("GI.Gtk.Objects.Widget#g:method:getWidth").
-- 
-- ==== Setters
-- [setActionName]("GI.Gtk.Interfaces.Actionable#g:method:setActionName"), [setActionTargetValue]("GI.Gtk.Interfaces.Actionable#g:method:setActionTargetValue"), [setCanFocus]("GI.Gtk.Objects.Widget#g:method:setCanFocus"), [setCanTarget]("GI.Gtk.Objects.Widget#g:method:setCanTarget"), [setChildVisible]("GI.Gtk.Objects.Widget#g:method:setChildVisible"), [setCssClasses]("GI.Gtk.Objects.Widget#g:method:setCssClasses"), [setCursor]("GI.Gtk.Objects.Widget#g:method:setCursor"), [setCursorFromName]("GI.Gtk.Objects.Widget#g:method:setCursorFromName"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDetailedActionName]("GI.Gtk.Interfaces.Actionable#g:method:setDetailedActionName"), [setDirection]("GI.Gtk.Objects.Widget#g:method:setDirection"), [setFocusChild]("GI.Gtk.Objects.Widget#g:method:setFocusChild"), [setFocusOnClick]("GI.Gtk.Objects.Widget#g:method:setFocusOnClick"), [setFocusable]("GI.Gtk.Objects.Widget#g:method:setFocusable"), [setFontMap]("GI.Gtk.Objects.Widget#g:method:setFontMap"), [setFontOptions]("GI.Gtk.Objects.Widget#g:method:setFontOptions"), [setHalign]("GI.Gtk.Objects.Widget#g:method:setHalign"), [setHasTooltip]("GI.Gtk.Objects.Widget#g:method:setHasTooltip"), [setHexpand]("GI.Gtk.Objects.Widget#g:method:setHexpand"), [setHexpandSet]("GI.Gtk.Objects.Widget#g:method:setHexpandSet"), [setLayoutManager]("GI.Gtk.Objects.Widget#g:method:setLayoutManager"), [setMarginBottom]("GI.Gtk.Objects.Widget#g:method:setMarginBottom"), [setMarginEnd]("GI.Gtk.Objects.Widget#g:method:setMarginEnd"), [setMarginStart]("GI.Gtk.Objects.Widget#g:method:setMarginStart"), [setMarginTop]("GI.Gtk.Objects.Widget#g:method:setMarginTop"), [setName]("GI.Gtk.Objects.Widget#g:method:setName"), [setOpacity]("GI.Gtk.Objects.Widget#g:method:setOpacity"), [setOverflow]("GI.Gtk.Objects.Widget#g:method:setOverflow"), [setParent]("GI.Gtk.Objects.Widget#g:method:setParent"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setReceivesDefault]("GI.Gtk.Objects.Widget#g:method:setReceivesDefault"), [setSensitive]("GI.Gtk.Objects.Widget#g:method:setSensitive"), [setSizeRequest]("GI.Gtk.Objects.Widget#g:method:setSizeRequest"), [setStateFlags]("GI.Gtk.Objects.Widget#g:method:setStateFlags"), [setTooltipMarkup]("GI.Gtk.Objects.Widget#g:method:setTooltipMarkup"), [setTooltipText]("GI.Gtk.Objects.Widget#g:method:setTooltipText"), [setValign]("GI.Gtk.Objects.Widget#g:method:setValign"), [setVexpand]("GI.Gtk.Objects.Widget#g:method:setVexpand"), [setVexpandSet]("GI.Gtk.Objects.Widget#g:method:setVexpandSet"), [setVisible]("GI.Gtk.Objects.Widget#g:method:setVisible").

#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.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.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Accessible as Gtk.Accessible
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 (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

-- | Type class for types which can be safely cast to `Actionable`, for instance with `toActionable`.
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]

-- | Cast to `Actionable`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toActionable :: (MIO.MonadIO m, IsActionable o) => o -> m Actionable
toActionable :: forall (m :: * -> *) o.
(MonadIO m, IsActionable o) =>
o -> m Actionable
toActionable = IO Actionable -> m Actionable
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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'
B.ManagedPtr.unsafeCastTo ManagedPtr Actionable -> Actionable
Actionable

-- | Convert 'Actionable' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe Actionable) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_actionable_get_type
    gvalueSet_ :: Ptr GValue -> Maybe Actionable -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Actionable
P.Nothing = Ptr GValue -> Ptr Actionable -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Actionable
forall a. Ptr a
FP.nullPtr :: FP.Ptr Actionable)
    gvalueSet_ Ptr GValue
gv (P.Just Actionable
obj) = Actionable -> (Ptr Actionable -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Actionable
obj (Ptr GValue -> Ptr Actionable -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe Actionable)
gvalueGet_ Ptr GValue
gv = do
        Ptr Actionable
ptr <- Ptr GValue -> IO (Ptr Actionable)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Actionable)
        if Ptr Actionable
ptr Ptr Actionable -> Ptr Actionable -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Actionable
forall a. Ptr a
FP.nullPtr
        then Actionable -> Maybe Actionable
forall a. a -> Maybe a
P.Just (Actionable -> Maybe Actionable)
-> IO Actionable -> IO (Maybe Actionable)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (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
        else Maybe Actionable -> IO (Maybe Actionable)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Actionable
forall a. Maybe a
P.Nothing
        
    

-- 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 :: forall (m :: * -> *) o.
(MonadIO m, IsActionable o) =>
o -> m (Maybe Text)
getActionableActionName o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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"

-- | 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 :: forall (m :: * -> *) o.
(MonadIO m, IsActionable o) =>
o -> Text -> m ()
setActionableActionName o
obj Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"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, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructActionableActionName :: forall o (m :: * -> *).
(IsActionable o, MonadIO m) =>
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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"action-name" (Text -> Maybe Text
forall a. a -> Maybe a
P.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 :: forall (m :: * -> *) o. (MonadIO m, IsActionable o) => 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
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Interfaces.Actionable.actionName"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Interfaces-Actionable.html#g:attr:actionName"
        })
#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 :: forall (m :: * -> *) o.
(MonadIO m, IsActionable o) =>
o -> m (Maybe GVariant)
getActionableActionTarget o
obj = IO (Maybe GVariant) -> m (Maybe GVariant)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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"

-- | 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 :: forall (m :: * -> *) o.
(MonadIO m, IsActionable o) =>
o -> GVariant -> m ()
setActionableActionTarget o
obj GVariant
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe 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)

-- | 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, MIO.MonadIO m) => GVariant -> m (GValueConstruct o)
constructActionableActionTarget :: forall o (m :: * -> *).
(IsActionable o, MonadIO m) =>
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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe 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)

-- | 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 :: forall (m :: * -> *) o. (MonadIO m, IsActionable o) => 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
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Interfaces.Actionable.actionTarget"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Interfaces-Actionable.html#g:attr:actionTarget"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Actionable
type instance O.AttributeList Actionable = ActionableAttributeList
type ActionableAttributeList = ('[ '("accessibleRole", Gtk.Accessible.AccessibleAccessibleRolePropertyInfo), '("actionName", ActionableActionNamePropertyInfo), '("actionTarget", ActionableActionTargetPropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("canTarget", Gtk.Widget.WidgetCanTargetPropertyInfo), '("cssClasses", Gtk.Widget.WidgetCssClassesPropertyInfo), '("cssName", Gtk.Widget.WidgetCssNamePropertyInfo), '("cursor", Gtk.Widget.WidgetCursorPropertyInfo), '("focusOnClick", Gtk.Widget.WidgetFocusOnClickPropertyInfo), '("focusable", Gtk.Widget.WidgetFocusablePropertyInfo), '("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), '("layoutManager", Gtk.Widget.WidgetLayoutManagerPropertyInfo), '("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), '("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 "actionSetEnabled" o = Gtk.Widget.WidgetActionSetEnabledMethodInfo
    ResolveActionableMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
    ResolveActionableMethod "activateAction" o = Gtk.Widget.WidgetActivateActionMethodInfo
    ResolveActionableMethod "activateDefault" o = Gtk.Widget.WidgetActivateDefaultMethodInfo
    ResolveActionableMethod "addController" o = Gtk.Widget.WidgetAddControllerMethodInfo
    ResolveActionableMethod "addCssClass" o = Gtk.Widget.WidgetAddCssClassMethodInfo
    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 "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 "contains" o = Gtk.Widget.WidgetContainsMethodInfo
    ResolveActionableMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
    ResolveActionableMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
    ResolveActionableMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
    ResolveActionableMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
    ResolveActionableMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveActionableMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveActionableMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveActionableMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
    ResolveActionableMethod "hasCssClass" o = Gtk.Widget.WidgetHasCssClassMethodInfo
    ResolveActionableMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
    ResolveActionableMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
    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 "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 "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
    ResolveActionableMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
    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 "pick" o = Gtk.Widget.WidgetPickMethodInfo
    ResolveActionableMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
    ResolveActionableMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
    ResolveActionableMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
    ResolveActionableMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
    ResolveActionableMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveActionableMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveActionableMethod "removeController" o = Gtk.Widget.WidgetRemoveControllerMethodInfo
    ResolveActionableMethod "removeCssClass" o = Gtk.Widget.WidgetRemoveCssClassMethodInfo
    ResolveActionableMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
    ResolveActionableMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
    ResolveActionableMethod "resetProperty" o = Gtk.Accessible.AccessibleResetPropertyMethodInfo
    ResolveActionableMethod "resetRelation" o = Gtk.Accessible.AccessibleResetRelationMethodInfo
    ResolveActionableMethod "resetState" o = Gtk.Accessible.AccessibleResetStateMethodInfo
    ResolveActionableMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveActionableMethod "shouldLayout" o = Gtk.Widget.WidgetShouldLayoutMethodInfo
    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 "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
    ResolveActionableMethod "updateProperty" o = Gtk.Accessible.AccessibleUpdatePropertyMethodInfo
    ResolveActionableMethod "updateRelation" o = Gtk.Accessible.AccessibleUpdateRelationMethodInfo
    ResolveActionableMethod "updateState" o = Gtk.Accessible.AccessibleUpdateStateMethodInfo
    ResolveActionableMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveActionableMethod "getAccessibleRole" o = Gtk.Accessible.AccessibleGetAccessibleRoleMethodInfo
    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 "getBuildableId" o = Gtk.Buildable.BuildableGetBuildableIdMethodInfo
    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 "getCssClasses" o = Gtk.Widget.WidgetGetCssClassesMethodInfo
    ResolveActionableMethod "getCssName" o = Gtk.Widget.WidgetGetCssNameMethodInfo
    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 "getFocusable" o = Gtk.Widget.WidgetGetFocusableMethodInfo
    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 "getHeight" o = Gtk.Widget.WidgetGetHeightMethodInfo
    ResolveActionableMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
    ResolveActionableMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
    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 "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
    ResolveActionableMethod "getNative" o = Gtk.Widget.WidgetGetNativeMethodInfo
    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 "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 "getSize" o = Gtk.Widget.WidgetGetSizeMethodInfo
    ResolveActionableMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
    ResolveActionableMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
    ResolveActionableMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
    ResolveActionableMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
    ResolveActionableMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
    ResolveActionableMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
    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 "setActionName" o = ActionableSetActionNameMethodInfo
    ResolveActionableMethod "setActionTargetValue" o = ActionableSetActionTargetValueMethodInfo
    ResolveActionableMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
    ResolveActionableMethod "setCanTarget" o = Gtk.Widget.WidgetSetCanTargetMethodInfo
    ResolveActionableMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
    ResolveActionableMethod "setCssClasses" o = Gtk.Widget.WidgetSetCssClassesMethodInfo
    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 "setFocusable" o = Gtk.Widget.WidgetSetFocusableMethodInfo
    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 "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 "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
    ResolveActionableMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
    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.OverloadedMethod 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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveActionableMethod t Actionable, O.OverloadedMethod info Actionable p, R.HasField t Actionable p) => R.HasField t Actionable p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveActionableMethod t Actionable, O.OverloadedMethodInfo info Actionable) => OL.IsLabel t (O.MethodProxy info Actionable) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#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@/.
actionableGetActionName ::
    (B.CallStack.HasCallStack, MonadIO m, IsActionable a) =>
    a
    -- ^ /@actionable@/: a @GtkActionable@ widget
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the action name
actionableGetActionName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsActionable a) =>
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.OverloadedMethod ActionableGetActionNameMethodInfo a signature where
    overloadedMethod = actionableGetActionName

instance O.OverloadedMethodInfo ActionableGetActionNameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Interfaces.Actionable.actionableGetActionName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Interfaces-Actionable.html#v: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@/.
actionableGetActionTargetValue ::
    (B.CallStack.HasCallStack, MonadIO m, IsActionable a) =>
    a
    -- ^ /@actionable@/: a @GtkActionable@ widget
    -> m (Maybe GVariant)
    -- ^ __Returns:__ the current target value
actionableGetActionTargetValue :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsActionable a) =>
a -> m (Maybe GVariant)
actionableGetActionTargetValue a
actionable = 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
$ 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'
    Maybe GVariant
maybeResult <- Ptr GVariant
-> (Ptr GVariant -> IO GVariant) -> IO (Maybe GVariant)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr GVariant
result ((Ptr GVariant -> IO GVariant) -> IO (Maybe GVariant))
-> (Ptr GVariant -> IO GVariant) -> IO (Maybe GVariant)
forall a b. (a -> b) -> a -> b
$ \Ptr GVariant
result' -> do
        GVariant
result'' <- Ptr GVariant -> IO GVariant
B.GVariant.newGVariantFromPtr Ptr GVariant
result'
        GVariant -> IO GVariant
forall (m :: * -> *) a. Monad m => a -> m a
return GVariant
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
actionable
    Maybe GVariant -> IO (Maybe GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe GVariant
maybeResult

#if defined(ENABLE_OVERLOADING)
data ActionableGetActionTargetValueMethodInfo
instance (signature ~ (m (Maybe GVariant)), MonadIO m, IsActionable a) => O.OverloadedMethod ActionableGetActionTargetValueMethodInfo a signature where
    overloadedMethod = actionableGetActionTargetValue

instance O.OverloadedMethodInfo ActionableGetActionTargetValueMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Interfaces.Actionable.actionableGetActionTargetValue",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Interfaces-Actionable.html#v: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" , 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 @GtkApplicationWindow@.
-- 
-- Names are of the form “win.save” or “app.quit” for actions on the
-- containing @GtkApplicationWindow@ or its associated @GtkApplication@,
-- respectively. This is the same form used for actions in the @GMenu@
-- associated with the window.
actionableSetActionName ::
    (B.CallStack.HasCallStack, MonadIO m, IsActionable a) =>
    a
    -- ^ /@actionable@/: a @GtkActionable@ widget
    -> Maybe (T.Text)
    -- ^ /@actionName@/: an action name
    -> m ()
actionableSetActionName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsActionable a) =>
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.OverloadedMethod ActionableSetActionNameMethodInfo a signature where
    overloadedMethod = actionableSetActionName

instance O.OverloadedMethodInfo ActionableSetActionNameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Interfaces.Actionable.actionableSetActionName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Interfaces-Actionable.html#v: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"
--                 , 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 @GtkActionable@ 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 @GAction@
-- 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 @GtkActionable@ widget
    -> Maybe (GVariant)
    -- ^ /@targetValue@/: a @GVariant@ to set as the target value
    -> m ()
actionableSetActionTargetValue :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsActionable a) =>
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.OverloadedMethod ActionableSetActionTargetValueMethodInfo a signature where
    overloadedMethod = actionableSetActionTargetValue

instance O.OverloadedMethodInfo ActionableSetActionTargetValueMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Interfaces.Actionable.actionableSetActionTargetValue",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Interfaces-Actionable.html#v: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'.
actionableSetDetailedActionName ::
    (B.CallStack.HasCallStack, MonadIO m, IsActionable a) =>
    a
    -- ^ /@actionable@/: a @GtkActionable@ widget
    -> T.Text
    -- ^ /@detailedActionName@/: the detailed action name
    -> m ()
actionableSetDetailedActionName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsActionable a) =>
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.OverloadedMethod ActionableSetDetailedActionNameMethodInfo a signature where
    overloadedMethod = actionableSetDetailedActionName

instance O.OverloadedMethodInfo ActionableSetDetailedActionNameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Interfaces.Actionable.actionableSetDetailedActionName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Interfaces-Actionable.html#v:actionableSetDetailedActionName"
        })


#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Actionable = ActionableSignalList
type ActionableSignalList = ('[ '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("directionChanged", Gtk.Widget.WidgetDirectionChangedSignalInfo), '("hide", Gtk.Widget.WidgetHideSignalInfo), '("keynavFailed", Gtk.Widget.WidgetKeynavFailedSignalInfo), '("map", Gtk.Widget.WidgetMapSignalInfo), '("mnemonicActivate", Gtk.Widget.WidgetMnemonicActivateSignalInfo), '("moveFocus", Gtk.Widget.WidgetMoveFocusSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("queryTooltip", Gtk.Widget.WidgetQueryTooltipSignalInfo), '("realize", Gtk.Widget.WidgetRealizeSignalInfo), '("show", Gtk.Widget.WidgetShowSignalInfo), '("stateFlagsChanged", Gtk.Widget.WidgetStateFlagsChangedSignalInfo), '("unmap", Gtk.Widget.WidgetUnmapSignalInfo), '("unrealize", Gtk.Widget.WidgetUnrealizeSignalInfo)] :: [(Symbol, *)])

#endif