{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (garetxe@gmail.com)
-}

module GI.Gtk.Objects.Action
    ( 

-- * Exported types
    Action(..)                              ,
    ActionK                                 ,
    toAction                                ,
    noAction                                ,


 -- * Methods
-- ** actionActivate
    actionActivate                          ,


-- ** actionBlockActivate
    actionBlockActivate                     ,


-- ** actionConnectAccelerator
    actionConnectAccelerator                ,


-- ** actionCreateIcon
    actionCreateIcon                        ,


-- ** actionCreateMenu
    actionCreateMenu                        ,


-- ** actionCreateMenuItem
    actionCreateMenuItem                    ,


-- ** actionCreateToolItem
    actionCreateToolItem                    ,


-- ** actionDisconnectAccelerator
    actionDisconnectAccelerator             ,


-- ** actionGetAccelClosure
    actionGetAccelClosure                   ,


-- ** actionGetAccelPath
    actionGetAccelPath                      ,


-- ** actionGetAlwaysShowImage
    actionGetAlwaysShowImage                ,


-- ** actionGetGicon
    actionGetGicon                          ,


-- ** actionGetIconName
    actionGetIconName                       ,


-- ** actionGetIsImportant
    actionGetIsImportant                    ,


-- ** actionGetLabel
    actionGetLabel                          ,


-- ** actionGetName
    actionGetName                           ,


-- ** actionGetProxies
    actionGetProxies                        ,


-- ** actionGetSensitive
    actionGetSensitive                      ,


-- ** actionGetShortLabel
    actionGetShortLabel                     ,


-- ** actionGetStockId
    actionGetStockId                        ,


-- ** actionGetTooltip
    actionGetTooltip                        ,


-- ** actionGetVisible
    actionGetVisible                        ,


-- ** actionGetVisibleHorizontal
    actionGetVisibleHorizontal              ,


-- ** actionGetVisibleVertical
    actionGetVisibleVertical                ,


-- ** actionIsSensitive
    actionIsSensitive                       ,


-- ** actionIsVisible
    actionIsVisible                         ,


-- ** actionNew
    actionNew                               ,


-- ** actionSetAccelGroup
    actionSetAccelGroup                     ,


-- ** actionSetAccelPath
    actionSetAccelPath                      ,


-- ** actionSetAlwaysShowImage
    actionSetAlwaysShowImage                ,


-- ** actionSetGicon
    actionSetGicon                          ,


-- ** actionSetIconName
    actionSetIconName                       ,


-- ** actionSetIsImportant
    actionSetIsImportant                    ,


-- ** actionSetLabel
    actionSetLabel                          ,


-- ** actionSetSensitive
    actionSetSensitive                      ,


-- ** actionSetShortLabel
    actionSetShortLabel                     ,


-- ** actionSetStockId
    actionSetStockId                        ,


-- ** actionSetTooltip
    actionSetTooltip                        ,


-- ** actionSetVisible
    actionSetVisible                        ,


-- ** actionSetVisibleHorizontal
    actionSetVisibleHorizontal              ,


-- ** actionSetVisibleVertical
    actionSetVisibleVertical                ,


-- ** actionUnblockActivate
    actionUnblockActivate                   ,




 -- * Properties
-- ** ActionGroup
    ActionActionGroupPropertyInfo           ,
    constructActionActionGroup              ,
    getActionActionGroup                    ,
    setActionActionGroup                    ,


-- ** AlwaysShowImage
    ActionAlwaysShowImagePropertyInfo       ,
    constructActionAlwaysShowImage          ,
    getActionAlwaysShowImage                ,
    setActionAlwaysShowImage                ,


-- ** Gicon
    ActionGiconPropertyInfo                 ,
    constructActionGicon                    ,
    getActionGicon                          ,
    setActionGicon                          ,


-- ** HideIfEmpty
    ActionHideIfEmptyPropertyInfo           ,
    constructActionHideIfEmpty              ,
    getActionHideIfEmpty                    ,
    setActionHideIfEmpty                    ,


-- ** IconName
    ActionIconNamePropertyInfo              ,
    constructActionIconName                 ,
    getActionIconName                       ,
    setActionIconName                       ,


-- ** IsImportant
    ActionIsImportantPropertyInfo           ,
    constructActionIsImportant              ,
    getActionIsImportant                    ,
    setActionIsImportant                    ,


-- ** Label
    ActionLabelPropertyInfo                 ,
    constructActionLabel                    ,
    getActionLabel                          ,
    setActionLabel                          ,


-- ** Name
    ActionNamePropertyInfo                  ,
    constructActionName                     ,
    getActionName                           ,


-- ** Sensitive
    ActionSensitivePropertyInfo             ,
    constructActionSensitive                ,
    getActionSensitive                      ,
    setActionSensitive                      ,


-- ** ShortLabel
    ActionShortLabelPropertyInfo            ,
    constructActionShortLabel               ,
    getActionShortLabel                     ,
    setActionShortLabel                     ,


-- ** StockId
    ActionStockIdPropertyInfo               ,
    constructActionStockId                  ,
    getActionStockId                        ,
    setActionStockId                        ,


-- ** Tooltip
    ActionTooltipPropertyInfo               ,
    constructActionTooltip                  ,
    getActionTooltip                        ,
    setActionTooltip                        ,


-- ** Visible
    ActionVisiblePropertyInfo               ,
    constructActionVisible                  ,
    getActionVisible                        ,
    setActionVisible                        ,


-- ** VisibleHorizontal
    ActionVisibleHorizontalPropertyInfo     ,
    constructActionVisibleHorizontal        ,
    getActionVisibleHorizontal              ,
    setActionVisibleHorizontal              ,


-- ** VisibleOverflown
    ActionVisibleOverflownPropertyInfo      ,
    constructActionVisibleOverflown         ,
    getActionVisibleOverflown               ,
    setActionVisibleOverflown               ,


-- ** VisibleVertical
    ActionVisibleVerticalPropertyInfo       ,
    constructActionVisibleVertical          ,
    getActionVisibleVertical                ,
    setActionVisibleVertical                ,




 -- * Signals
-- ** Activate
    ActionActivateCallback                  ,
    ActionActivateCallbackC                 ,
    ActionActivateSignalInfo                ,
    actionActivateCallbackWrapper           ,
    actionActivateClosure                   ,
    afterActionActivate                     ,
    mkActionActivateCallback                ,
    noActionActivateCallback                ,
    onActionActivate                        ,




    ) where

import Prelude ()
import Data.GI.Base.ShortPrelude

import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map

import GI.Gtk.Types
import GI.Gtk.Callbacks
import qualified GI.GObject as GObject
import qualified GI.Gio as Gio

newtype Action = Action (ForeignPtr Action)
foreign import ccall "gtk_action_get_type"
    c_gtk_action_get_type :: IO GType

type instance ParentTypes Action = ActionParentTypes
type ActionParentTypes = '[GObject.Object, Buildable]

instance GObject Action where
    gobjectIsInitiallyUnowned _ = False
    gobjectType _ = c_gtk_action_get_type
    

class GObject o => ActionK o
instance (GObject o, IsDescendantOf Action o) => ActionK o

toAction :: ActionK o => o -> IO Action
toAction = unsafeCastTo Action

noAction :: Maybe Action
noAction = Nothing

-- signal Action::activate
type ActionActivateCallback =
    IO ()

noActionActivateCallback :: Maybe ActionActivateCallback
noActionActivateCallback = Nothing

type ActionActivateCallbackC =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO ()

foreign import ccall "wrapper"
    mkActionActivateCallback :: ActionActivateCallbackC -> IO (FunPtr ActionActivateCallbackC)

actionActivateClosure :: ActionActivateCallback -> IO Closure
actionActivateClosure cb = newCClosure =<< mkActionActivateCallback wrapped
    where wrapped = actionActivateCallbackWrapper cb

actionActivateCallbackWrapper ::
    ActionActivateCallback ->
    Ptr () ->
    Ptr () ->
    IO ()
actionActivateCallbackWrapper _cb _ _ = do
    _cb 

onActionActivate :: (GObject a, MonadIO m) => a -> ActionActivateCallback -> m SignalHandlerId
onActionActivate obj cb = liftIO $ connectActionActivate obj cb SignalConnectBefore
afterActionActivate :: (GObject a, MonadIO m) => a -> ActionActivateCallback -> m SignalHandlerId
afterActionActivate obj cb = connectActionActivate obj cb SignalConnectAfter

connectActionActivate :: (GObject a, MonadIO m) =>
                         a -> ActionActivateCallback -> SignalConnectMode -> m SignalHandlerId
connectActionActivate obj cb after = liftIO $ do
    cb' <- mkActionActivateCallback (actionActivateCallbackWrapper cb)
    connectSignalFunPtr obj "activate" cb' after

-- VVV Prop "action-group"
   -- Type: TInterface "Gtk" "ActionGroup"
   -- Flags: [PropertyReadable,PropertyWritable]

getActionActionGroup :: (MonadIO m, ActionK o) => o -> m ActionGroup
getActionActionGroup obj = liftIO $ getObjectPropertyObject obj "action-group" ActionGroup

setActionActionGroup :: (MonadIO m, ActionK o, ActionGroupK a) => o -> a -> m ()
setActionActionGroup obj val = liftIO $ setObjectPropertyObject obj "action-group" val

constructActionActionGroup :: (ActionGroupK a) => a -> IO ([Char], GValue)
constructActionActionGroup val = constructObjectPropertyObject "action-group" val

data ActionActionGroupPropertyInfo
instance AttrInfo ActionActionGroupPropertyInfo where
    type AttrAllowedOps ActionActionGroupPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint ActionActionGroupPropertyInfo = ActionGroupK
    type AttrBaseTypeConstraint ActionActionGroupPropertyInfo = ActionK
    type AttrGetType ActionActionGroupPropertyInfo = ActionGroup
    type AttrLabel ActionActionGroupPropertyInfo = "Action::action-group"
    attrGet _ = getActionActionGroup
    attrSet _ = setActionActionGroup
    attrConstruct _ = constructActionActionGroup

-- VVV Prop "always-show-image"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct]

getActionAlwaysShowImage :: (MonadIO m, ActionK o) => o -> m Bool
getActionAlwaysShowImage obj = liftIO $ getObjectPropertyBool obj "always-show-image"

setActionAlwaysShowImage :: (MonadIO m, ActionK o) => o -> Bool -> m ()
setActionAlwaysShowImage obj val = liftIO $ setObjectPropertyBool obj "always-show-image" val

constructActionAlwaysShowImage :: Bool -> IO ([Char], GValue)
constructActionAlwaysShowImage val = constructObjectPropertyBool "always-show-image" val

data ActionAlwaysShowImagePropertyInfo
instance AttrInfo ActionAlwaysShowImagePropertyInfo where
    type AttrAllowedOps ActionAlwaysShowImagePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint ActionAlwaysShowImagePropertyInfo = (~) Bool
    type AttrBaseTypeConstraint ActionAlwaysShowImagePropertyInfo = ActionK
    type AttrGetType ActionAlwaysShowImagePropertyInfo = Bool
    type AttrLabel ActionAlwaysShowImagePropertyInfo = "Action::always-show-image"
    attrGet _ = getActionAlwaysShowImage
    attrSet _ = setActionAlwaysShowImage
    attrConstruct _ = constructActionAlwaysShowImage

-- VVV Prop "gicon"
   -- Type: TInterface "Gio" "Icon"
   -- Flags: [PropertyReadable,PropertyWritable]

getActionGicon :: (MonadIO m, ActionK o) => o -> m Gio.Icon
getActionGicon obj = liftIO $ getObjectPropertyObject obj "gicon" Gio.Icon

setActionGicon :: (MonadIO m, ActionK o, Gio.IconK a) => o -> a -> m ()
setActionGicon obj val = liftIO $ setObjectPropertyObject obj "gicon" val

constructActionGicon :: (Gio.IconK a) => a -> IO ([Char], GValue)
constructActionGicon val = constructObjectPropertyObject "gicon" val

data ActionGiconPropertyInfo
instance AttrInfo ActionGiconPropertyInfo where
    type AttrAllowedOps ActionGiconPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint ActionGiconPropertyInfo = Gio.IconK
    type AttrBaseTypeConstraint ActionGiconPropertyInfo = ActionK
    type AttrGetType ActionGiconPropertyInfo = Gio.Icon
    type AttrLabel ActionGiconPropertyInfo = "Action::gicon"
    attrGet _ = getActionGicon
    attrSet _ = setActionGicon
    attrConstruct _ = constructActionGicon

-- VVV Prop "hide-if-empty"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getActionHideIfEmpty :: (MonadIO m, ActionK o) => o -> m Bool
getActionHideIfEmpty obj = liftIO $ getObjectPropertyBool obj "hide-if-empty"

setActionHideIfEmpty :: (MonadIO m, ActionK o) => o -> Bool -> m ()
setActionHideIfEmpty obj val = liftIO $ setObjectPropertyBool obj "hide-if-empty" val

constructActionHideIfEmpty :: Bool -> IO ([Char], GValue)
constructActionHideIfEmpty val = constructObjectPropertyBool "hide-if-empty" val

data ActionHideIfEmptyPropertyInfo
instance AttrInfo ActionHideIfEmptyPropertyInfo where
    type AttrAllowedOps ActionHideIfEmptyPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint ActionHideIfEmptyPropertyInfo = (~) Bool
    type AttrBaseTypeConstraint ActionHideIfEmptyPropertyInfo = ActionK
    type AttrGetType ActionHideIfEmptyPropertyInfo = Bool
    type AttrLabel ActionHideIfEmptyPropertyInfo = "Action::hide-if-empty"
    attrGet _ = getActionHideIfEmpty
    attrSet _ = setActionHideIfEmpty
    attrConstruct _ = constructActionHideIfEmpty

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

getActionIconName :: (MonadIO m, ActionK o) => o -> m T.Text
getActionIconName obj = liftIO $ getObjectPropertyString obj "icon-name"

setActionIconName :: (MonadIO m, ActionK o) => o -> T.Text -> m ()
setActionIconName obj val = liftIO $ setObjectPropertyString obj "icon-name" val

constructActionIconName :: T.Text -> IO ([Char], GValue)
constructActionIconName val = constructObjectPropertyString "icon-name" val

data ActionIconNamePropertyInfo
instance AttrInfo ActionIconNamePropertyInfo where
    type AttrAllowedOps ActionIconNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint ActionIconNamePropertyInfo = (~) T.Text
    type AttrBaseTypeConstraint ActionIconNamePropertyInfo = ActionK
    type AttrGetType ActionIconNamePropertyInfo = T.Text
    type AttrLabel ActionIconNamePropertyInfo = "Action::icon-name"
    attrGet _ = getActionIconName
    attrSet _ = setActionIconName
    attrConstruct _ = constructActionIconName

-- VVV Prop "is-important"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getActionIsImportant :: (MonadIO m, ActionK o) => o -> m Bool
getActionIsImportant obj = liftIO $ getObjectPropertyBool obj "is-important"

setActionIsImportant :: (MonadIO m, ActionK o) => o -> Bool -> m ()
setActionIsImportant obj val = liftIO $ setObjectPropertyBool obj "is-important" val

constructActionIsImportant :: Bool -> IO ([Char], GValue)
constructActionIsImportant val = constructObjectPropertyBool "is-important" val

data ActionIsImportantPropertyInfo
instance AttrInfo ActionIsImportantPropertyInfo where
    type AttrAllowedOps ActionIsImportantPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint ActionIsImportantPropertyInfo = (~) Bool
    type AttrBaseTypeConstraint ActionIsImportantPropertyInfo = ActionK
    type AttrGetType ActionIsImportantPropertyInfo = Bool
    type AttrLabel ActionIsImportantPropertyInfo = "Action::is-important"
    attrGet _ = getActionIsImportant
    attrSet _ = setActionIsImportant
    attrConstruct _ = constructActionIsImportant

-- VVV Prop "label"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]

getActionLabel :: (MonadIO m, ActionK o) => o -> m T.Text
getActionLabel obj = liftIO $ getObjectPropertyString obj "label"

setActionLabel :: (MonadIO m, ActionK o) => o -> T.Text -> m ()
setActionLabel obj val = liftIO $ setObjectPropertyString obj "label" val

constructActionLabel :: T.Text -> IO ([Char], GValue)
constructActionLabel val = constructObjectPropertyString "label" val

data ActionLabelPropertyInfo
instance AttrInfo ActionLabelPropertyInfo where
    type AttrAllowedOps ActionLabelPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint ActionLabelPropertyInfo = (~) T.Text
    type AttrBaseTypeConstraint ActionLabelPropertyInfo = ActionK
    type AttrGetType ActionLabelPropertyInfo = T.Text
    type AttrLabel ActionLabelPropertyInfo = "Action::label"
    attrGet _ = getActionLabel
    attrSet _ = setActionLabel
    attrConstruct _ = constructActionLabel

-- VVV Prop "name"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]

getActionName :: (MonadIO m, ActionK o) => o -> m T.Text
getActionName obj = liftIO $ getObjectPropertyString obj "name"

constructActionName :: T.Text -> IO ([Char], GValue)
constructActionName val = constructObjectPropertyString "name" val

data ActionNamePropertyInfo
instance AttrInfo ActionNamePropertyInfo where
    type AttrAllowedOps ActionNamePropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint ActionNamePropertyInfo = (~) T.Text
    type AttrBaseTypeConstraint ActionNamePropertyInfo = ActionK
    type AttrGetType ActionNamePropertyInfo = T.Text
    type AttrLabel ActionNamePropertyInfo = "Action::name"
    attrGet _ = getActionName
    attrSet _ = undefined
    attrConstruct _ = constructActionName

-- VVV Prop "sensitive"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getActionSensitive :: (MonadIO m, ActionK o) => o -> m Bool
getActionSensitive obj = liftIO $ getObjectPropertyBool obj "sensitive"

setActionSensitive :: (MonadIO m, ActionK o) => o -> Bool -> m ()
setActionSensitive obj val = liftIO $ setObjectPropertyBool obj "sensitive" val

constructActionSensitive :: Bool -> IO ([Char], GValue)
constructActionSensitive val = constructObjectPropertyBool "sensitive" val

data ActionSensitivePropertyInfo
instance AttrInfo ActionSensitivePropertyInfo where
    type AttrAllowedOps ActionSensitivePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint ActionSensitivePropertyInfo = (~) Bool
    type AttrBaseTypeConstraint ActionSensitivePropertyInfo = ActionK
    type AttrGetType ActionSensitivePropertyInfo = Bool
    type AttrLabel ActionSensitivePropertyInfo = "Action::sensitive"
    attrGet _ = getActionSensitive
    attrSet _ = setActionSensitive
    attrConstruct _ = constructActionSensitive

-- VVV Prop "short-label"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]

getActionShortLabel :: (MonadIO m, ActionK o) => o -> m T.Text
getActionShortLabel obj = liftIO $ getObjectPropertyString obj "short-label"

setActionShortLabel :: (MonadIO m, ActionK o) => o -> T.Text -> m ()
setActionShortLabel obj val = liftIO $ setObjectPropertyString obj "short-label" val

constructActionShortLabel :: T.Text -> IO ([Char], GValue)
constructActionShortLabel val = constructObjectPropertyString "short-label" val

data ActionShortLabelPropertyInfo
instance AttrInfo ActionShortLabelPropertyInfo where
    type AttrAllowedOps ActionShortLabelPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint ActionShortLabelPropertyInfo = (~) T.Text
    type AttrBaseTypeConstraint ActionShortLabelPropertyInfo = ActionK
    type AttrGetType ActionShortLabelPropertyInfo = T.Text
    type AttrLabel ActionShortLabelPropertyInfo = "Action::short-label"
    attrGet _ = getActionShortLabel
    attrSet _ = setActionShortLabel
    attrConstruct _ = constructActionShortLabel

-- VVV Prop "stock-id"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]

getActionStockId :: (MonadIO m, ActionK o) => o -> m T.Text
getActionStockId obj = liftIO $ getObjectPropertyString obj "stock-id"

setActionStockId :: (MonadIO m, ActionK o) => o -> T.Text -> m ()
setActionStockId obj val = liftIO $ setObjectPropertyString obj "stock-id" val

constructActionStockId :: T.Text -> IO ([Char], GValue)
constructActionStockId val = constructObjectPropertyString "stock-id" val

data ActionStockIdPropertyInfo
instance AttrInfo ActionStockIdPropertyInfo where
    type AttrAllowedOps ActionStockIdPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint ActionStockIdPropertyInfo = (~) T.Text
    type AttrBaseTypeConstraint ActionStockIdPropertyInfo = ActionK
    type AttrGetType ActionStockIdPropertyInfo = T.Text
    type AttrLabel ActionStockIdPropertyInfo = "Action::stock-id"
    attrGet _ = getActionStockId
    attrSet _ = setActionStockId
    attrConstruct _ = constructActionStockId

-- VVV Prop "tooltip"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]

getActionTooltip :: (MonadIO m, ActionK o) => o -> m T.Text
getActionTooltip obj = liftIO $ getObjectPropertyString obj "tooltip"

setActionTooltip :: (MonadIO m, ActionK o) => o -> T.Text -> m ()
setActionTooltip obj val = liftIO $ setObjectPropertyString obj "tooltip" val

constructActionTooltip :: T.Text -> IO ([Char], GValue)
constructActionTooltip val = constructObjectPropertyString "tooltip" val

data ActionTooltipPropertyInfo
instance AttrInfo ActionTooltipPropertyInfo where
    type AttrAllowedOps ActionTooltipPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint ActionTooltipPropertyInfo = (~) T.Text
    type AttrBaseTypeConstraint ActionTooltipPropertyInfo = ActionK
    type AttrGetType ActionTooltipPropertyInfo = T.Text
    type AttrLabel ActionTooltipPropertyInfo = "Action::tooltip"
    attrGet _ = getActionTooltip
    attrSet _ = setActionTooltip
    attrConstruct _ = constructActionTooltip

-- VVV Prop "visible"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getActionVisible :: (MonadIO m, ActionK o) => o -> m Bool
getActionVisible obj = liftIO $ getObjectPropertyBool obj "visible"

setActionVisible :: (MonadIO m, ActionK o) => o -> Bool -> m ()
setActionVisible obj val = liftIO $ setObjectPropertyBool obj "visible" val

constructActionVisible :: Bool -> IO ([Char], GValue)
constructActionVisible val = constructObjectPropertyBool "visible" val

data ActionVisiblePropertyInfo
instance AttrInfo ActionVisiblePropertyInfo where
    type AttrAllowedOps ActionVisiblePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint ActionVisiblePropertyInfo = (~) Bool
    type AttrBaseTypeConstraint ActionVisiblePropertyInfo = ActionK
    type AttrGetType ActionVisiblePropertyInfo = Bool
    type AttrLabel ActionVisiblePropertyInfo = "Action::visible"
    attrGet _ = getActionVisible
    attrSet _ = setActionVisible
    attrConstruct _ = constructActionVisible

-- VVV Prop "visible-horizontal"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getActionVisibleHorizontal :: (MonadIO m, ActionK o) => o -> m Bool
getActionVisibleHorizontal obj = liftIO $ getObjectPropertyBool obj "visible-horizontal"

setActionVisibleHorizontal :: (MonadIO m, ActionK o) => o -> Bool -> m ()
setActionVisibleHorizontal obj val = liftIO $ setObjectPropertyBool obj "visible-horizontal" val

constructActionVisibleHorizontal :: Bool -> IO ([Char], GValue)
constructActionVisibleHorizontal val = constructObjectPropertyBool "visible-horizontal" val

data ActionVisibleHorizontalPropertyInfo
instance AttrInfo ActionVisibleHorizontalPropertyInfo where
    type AttrAllowedOps ActionVisibleHorizontalPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint ActionVisibleHorizontalPropertyInfo = (~) Bool
    type AttrBaseTypeConstraint ActionVisibleHorizontalPropertyInfo = ActionK
    type AttrGetType ActionVisibleHorizontalPropertyInfo = Bool
    type AttrLabel ActionVisibleHorizontalPropertyInfo = "Action::visible-horizontal"
    attrGet _ = getActionVisibleHorizontal
    attrSet _ = setActionVisibleHorizontal
    attrConstruct _ = constructActionVisibleHorizontal

-- VVV Prop "visible-overflown"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getActionVisibleOverflown :: (MonadIO m, ActionK o) => o -> m Bool
getActionVisibleOverflown obj = liftIO $ getObjectPropertyBool obj "visible-overflown"

setActionVisibleOverflown :: (MonadIO m, ActionK o) => o -> Bool -> m ()
setActionVisibleOverflown obj val = liftIO $ setObjectPropertyBool obj "visible-overflown" val

constructActionVisibleOverflown :: Bool -> IO ([Char], GValue)
constructActionVisibleOverflown val = constructObjectPropertyBool "visible-overflown" val

data ActionVisibleOverflownPropertyInfo
instance AttrInfo ActionVisibleOverflownPropertyInfo where
    type AttrAllowedOps ActionVisibleOverflownPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint ActionVisibleOverflownPropertyInfo = (~) Bool
    type AttrBaseTypeConstraint ActionVisibleOverflownPropertyInfo = ActionK
    type AttrGetType ActionVisibleOverflownPropertyInfo = Bool
    type AttrLabel ActionVisibleOverflownPropertyInfo = "Action::visible-overflown"
    attrGet _ = getActionVisibleOverflown
    attrSet _ = setActionVisibleOverflown
    attrConstruct _ = constructActionVisibleOverflown

-- VVV Prop "visible-vertical"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getActionVisibleVertical :: (MonadIO m, ActionK o) => o -> m Bool
getActionVisibleVertical obj = liftIO $ getObjectPropertyBool obj "visible-vertical"

setActionVisibleVertical :: (MonadIO m, ActionK o) => o -> Bool -> m ()
setActionVisibleVertical obj val = liftIO $ setObjectPropertyBool obj "visible-vertical" val

constructActionVisibleVertical :: Bool -> IO ([Char], GValue)
constructActionVisibleVertical val = constructObjectPropertyBool "visible-vertical" val

data ActionVisibleVerticalPropertyInfo
instance AttrInfo ActionVisibleVerticalPropertyInfo where
    type AttrAllowedOps ActionVisibleVerticalPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint ActionVisibleVerticalPropertyInfo = (~) Bool
    type AttrBaseTypeConstraint ActionVisibleVerticalPropertyInfo = ActionK
    type AttrGetType ActionVisibleVerticalPropertyInfo = Bool
    type AttrLabel ActionVisibleVerticalPropertyInfo = "Action::visible-vertical"
    attrGet _ = getActionVisibleVertical
    attrSet _ = setActionVisibleVertical
    attrConstruct _ = constructActionVisibleVertical

type instance AttributeList Action = ActionAttributeList
type ActionAttributeList = ('[ '("action-group", ActionActionGroupPropertyInfo), '("always-show-image", ActionAlwaysShowImagePropertyInfo), '("gicon", ActionGiconPropertyInfo), '("hide-if-empty", ActionHideIfEmptyPropertyInfo), '("icon-name", ActionIconNamePropertyInfo), '("is-important", ActionIsImportantPropertyInfo), '("label", ActionLabelPropertyInfo), '("name", ActionNamePropertyInfo), '("sensitive", ActionSensitivePropertyInfo), '("short-label", ActionShortLabelPropertyInfo), '("stock-id", ActionStockIdPropertyInfo), '("tooltip", ActionTooltipPropertyInfo), '("visible", ActionVisiblePropertyInfo), '("visible-horizontal", ActionVisibleHorizontalPropertyInfo), '("visible-overflown", ActionVisibleOverflownPropertyInfo), '("visible-vertical", ActionVisibleVerticalPropertyInfo)] :: [(Symbol, *)])

data ActionActivateSignalInfo
instance SignalInfo ActionActivateSignalInfo where
    type HaskellCallbackType ActionActivateSignalInfo = ActionActivateCallback
    connectSignal _ = connectActionActivate

type instance SignalList Action = ActionSignalList
type ActionSignalList = ('[ '("activate", ActionActivateSignalInfo), '("notify", GObject.ObjectNotifySignalInfo), '("notify::[property]", GObjectNotifySignalInfo)] :: [(Symbol, *)])

-- method Action::new
-- method type : Constructor
-- Args : [Arg {argName = "name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "label", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "tooltip", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "stock_id", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "label", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "tooltip", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "stock_id", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gtk" "Action"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_new" gtk_action_new :: 
    CString ->                              -- name : TBasicType TUTF8
    CString ->                              -- label : TBasicType TUTF8
    CString ->                              -- tooltip : TBasicType TUTF8
    CString ->                              -- stock_id : TBasicType TUTF8
    IO (Ptr Action)

{-# DEPRECATED actionNew ["(Since version 3.10)","Use #GAction instead, associating it to a widget with","#GtkActionable or creating a #GtkMenu with gtk_menu_new_from_model()"]#-}
actionNew ::
    (MonadIO m) =>
    T.Text ->                               -- name
    Maybe (T.Text) ->                       -- label
    Maybe (T.Text) ->                       -- tooltip
    Maybe (T.Text) ->                       -- stock_id
    m Action
actionNew name label tooltip stock_id = liftIO $ do
    name' <- textToCString name
    maybeLabel <- case label of
        Nothing -> return nullPtr
        Just jLabel -> do
            jLabel' <- textToCString jLabel
            return jLabel'
    maybeTooltip <- case tooltip of
        Nothing -> return nullPtr
        Just jTooltip -> do
            jTooltip' <- textToCString jTooltip
            return jTooltip'
    maybeStock_id <- case stock_id of
        Nothing -> return nullPtr
        Just jStock_id -> do
            jStock_id' <- textToCString jStock_id
            return jStock_id'
    result <- gtk_action_new name' maybeLabel maybeTooltip maybeStock_id
    checkUnexpectedReturnNULL "gtk_action_new" result
    result' <- (wrapObject Action) result
    freeMem name'
    freeMem maybeLabel
    freeMem maybeTooltip
    freeMem maybeStock_id
    return result'

-- method Action::activate
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_activate" gtk_action_activate :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    IO ()

{-# DEPRECATED actionActivate ["(Since version 3.10)","Use g_action_group_activate_action() on a #GAction instead"]#-}
actionActivate ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    m ()
actionActivate _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    gtk_action_activate _obj'
    touchManagedPtr _obj
    return ()

-- method Action::block_activate
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_block_activate" gtk_action_block_activate :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    IO ()

{-# DEPRECATED actionBlockActivate ["(Since version 3.10)","Use g_simple_action_set_enabled() to disable the","#GSimpleAction instead"]#-}
actionBlockActivate ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    m ()
actionBlockActivate _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    gtk_action_block_activate _obj'
    touchManagedPtr _obj
    return ()

-- method Action::connect_accelerator
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_connect_accelerator" gtk_action_connect_accelerator :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    IO ()

{-# DEPRECATED actionConnectAccelerator ["(Since version 3.10)","Use #GAction and the accelerator group on an associated","#GtkMenu instead"]#-}
actionConnectAccelerator ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    m ()
actionConnectAccelerator _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    gtk_action_connect_accelerator _obj'
    touchManagedPtr _obj
    return ()

-- method Action::create_icon
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "icon_size", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "icon_size", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gtk" "Widget"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_create_icon" gtk_action_create_icon :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    Int32 ->                                -- icon_size : TBasicType TInt32
    IO (Ptr Widget)

{-# DEPRECATED actionCreateIcon ["(Since version 3.10)","Use g_menu_item_set_icon() to set an icon on a #GMenuItem,","or gtk_container_add() to add a #GtkImage to a #GtkButton"]#-}
actionCreateIcon ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    Int32 ->                                -- icon_size
    m Widget
actionCreateIcon _obj icon_size = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_action_create_icon _obj' icon_size
    checkUnexpectedReturnNULL "gtk_action_create_icon" result
    result' <- (newObject Widget) result
    touchManagedPtr _obj
    return result'

-- method Action::create_menu
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gtk" "Widget"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_create_menu" gtk_action_create_menu :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    IO (Ptr Widget)

{-# DEPRECATED actionCreateMenu ["(Since version 3.10)","Use #GAction and #GMenuModel instead, and create a","#GtkMenu with gtk_menu_new_from_model()"]#-}
actionCreateMenu ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    m Widget
actionCreateMenu _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_action_create_menu _obj'
    checkUnexpectedReturnNULL "gtk_action_create_menu" result
    result' <- (newObject Widget) result
    touchManagedPtr _obj
    return result'

-- method Action::create_menu_item
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gtk" "Widget"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_create_menu_item" gtk_action_create_menu_item :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    IO (Ptr Widget)

{-# DEPRECATED actionCreateMenuItem ["(Since version 3.10)","Use g_menu_item_new() and associate it with a #GAction","instead."]#-}
actionCreateMenuItem ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    m Widget
actionCreateMenuItem _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_action_create_menu_item _obj'
    checkUnexpectedReturnNULL "gtk_action_create_menu_item" result
    result' <- (newObject Widget) result
    touchManagedPtr _obj
    return result'

-- method Action::create_tool_item
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gtk" "Widget"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_create_tool_item" gtk_action_create_tool_item :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    IO (Ptr Widget)

{-# DEPRECATED actionCreateToolItem ["(Since version 3.10)","Use a #GtkToolItem and associate it with a #GAction using","gtk_actionable_set_action_name() instead"]#-}
actionCreateToolItem ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    m Widget
actionCreateToolItem _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_action_create_tool_item _obj'
    checkUnexpectedReturnNULL "gtk_action_create_tool_item" result
    result' <- (newObject Widget) result
    touchManagedPtr _obj
    return result'

-- method Action::disconnect_accelerator
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_disconnect_accelerator" gtk_action_disconnect_accelerator :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    IO ()

{-# DEPRECATED actionDisconnectAccelerator ["(Since version 3.10)","Use #GAction and the accelerator group on an associated","#GtkMenu instead"]#-}
actionDisconnectAccelerator ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    m ()
actionDisconnectAccelerator _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    gtk_action_disconnect_accelerator _obj'
    touchManagedPtr _obj
    return ()

-- method Action::get_accel_closure
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "GObject" "Closure"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_get_accel_closure" gtk_action_get_accel_closure :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    IO (Ptr Closure)

{-# DEPRECATED actionGetAccelClosure ["(Since version 3.10)","Use #GAction and #GtkMenu instead, which have no","equivalent for getting the accel closure"]#-}
actionGetAccelClosure ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    m Closure
actionGetAccelClosure _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_action_get_accel_closure _obj'
    checkUnexpectedReturnNULL "gtk_action_get_accel_closure" result
    result' <- (newBoxed Closure) result
    touchManagedPtr _obj
    return result'

-- method Action::get_accel_path
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_get_accel_path" gtk_action_get_accel_path :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    IO CString

{-# DEPRECATED actionGetAccelPath ["(Since version 3.10)","Use #GAction and the accelerator path on an associated","#GtkMenu instead"]#-}
actionGetAccelPath ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    m T.Text
actionGetAccelPath _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_action_get_accel_path _obj'
    checkUnexpectedReturnNULL "gtk_action_get_accel_path" result
    result' <- cstringToText result
    touchManagedPtr _obj
    return result'

-- method Action::get_always_show_image
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_get_always_show_image" gtk_action_get_always_show_image :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    IO CInt

{-# DEPRECATED actionGetAlwaysShowImage ["(Since version 3.10)","Use g_menu_item_get_attribute_value() on a #GMenuItem","instead"]#-}
actionGetAlwaysShowImage ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    m Bool
actionGetAlwaysShowImage _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_action_get_always_show_image _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method Action::get_gicon
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gio" "Icon"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_get_gicon" gtk_action_get_gicon :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    IO (Ptr Gio.Icon)

{-# DEPRECATED actionGetGicon ["(Since version 3.10)","Use #GAction instead, and","g_menu_item_get_attribute_value() to get an icon from a #GMenuItem","associated with a #GAction"]#-}
actionGetGicon ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    m Gio.Icon
actionGetGicon _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_action_get_gicon _obj'
    checkUnexpectedReturnNULL "gtk_action_get_gicon" result
    result' <- (newObject Gio.Icon) result
    touchManagedPtr _obj
    return result'

-- method Action::get_icon_name
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_get_icon_name" gtk_action_get_icon_name :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    IO CString

{-# DEPRECATED actionGetIconName ["(Since version 3.10)","Use #GAction instead, and","g_menu_item_get_attribute_value() to get an icon from a #GMenuItem","associated with a #GAction"]#-}
actionGetIconName ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    m T.Text
actionGetIconName _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_action_get_icon_name _obj'
    checkUnexpectedReturnNULL "gtk_action_get_icon_name" result
    result' <- cstringToText result
    touchManagedPtr _obj
    return result'

-- method Action::get_is_important
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_get_is_important" gtk_action_get_is_important :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    IO CInt

{-# DEPRECATED actionGetIsImportant ["(Since version 3.10)","Use #GAction instead, and control and monitor whether","labels are shown directly"]#-}
actionGetIsImportant ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    m Bool
actionGetIsImportant _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_action_get_is_important _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method Action::get_label
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_get_label" gtk_action_get_label :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    IO CString

{-# DEPRECATED actionGetLabel ["(Since version 3.10)","Use #GAction instead, and get a label from a menu item","with g_menu_item_get_attribute_value(). For #GtkActionable widgets, use the","widget-specific API to get a label"]#-}
actionGetLabel ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    m T.Text
actionGetLabel _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_action_get_label _obj'
    checkUnexpectedReturnNULL "gtk_action_get_label" result
    result' <- cstringToText result
    touchManagedPtr _obj
    return result'

-- method Action::get_name
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_get_name" gtk_action_get_name :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    IO CString

{-# DEPRECATED actionGetName ["(Since version 3.10)","Use g_action_get_name() on a #GAction instead"]#-}
actionGetName ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    m T.Text
actionGetName _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_action_get_name _obj'
    checkUnexpectedReturnNULL "gtk_action_get_name" result
    result' <- cstringToText result
    touchManagedPtr _obj
    return result'

-- method Action::get_proxies
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TGSList (TInterface "Gtk" "Widget")
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_get_proxies" gtk_action_get_proxies :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    IO (Ptr (GSList (Ptr Widget)))

{-# DEPRECATED actionGetProxies ["(Since version 3.10)"]#-}
actionGetProxies ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    m [Widget]
actionGetProxies _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_action_get_proxies _obj'
    checkUnexpectedReturnNULL "gtk_action_get_proxies" result
    result' <- unpackGSList result
    result'' <- mapM (newObject Widget) result'
    touchManagedPtr _obj
    return result''

-- method Action::get_sensitive
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_get_sensitive" gtk_action_get_sensitive :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    IO CInt

{-# DEPRECATED actionGetSensitive ["(Since version 3.10)","Use g_action_get_enabled() on a #GAction","instead"]#-}
actionGetSensitive ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    m Bool
actionGetSensitive _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_action_get_sensitive _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method Action::get_short_label
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_get_short_label" gtk_action_get_short_label :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    IO CString

{-# DEPRECATED actionGetShortLabel ["(Since version 3.10)","Use #GAction instead, which has no equivalent of short","labels"]#-}
actionGetShortLabel ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    m T.Text
actionGetShortLabel _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_action_get_short_label _obj'
    checkUnexpectedReturnNULL "gtk_action_get_short_label" result
    result' <- cstringToText result
    touchManagedPtr _obj
    return result'

-- method Action::get_stock_id
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_get_stock_id" gtk_action_get_stock_id :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    IO CString

{-# DEPRECATED actionGetStockId ["(Since version 3.10)","Use #GAction instead, which has no equivalent of stock","items"]#-}
actionGetStockId ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    m T.Text
actionGetStockId _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_action_get_stock_id _obj'
    checkUnexpectedReturnNULL "gtk_action_get_stock_id" result
    result' <- cstringToText result
    touchManagedPtr _obj
    return result'

-- method Action::get_tooltip
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_get_tooltip" gtk_action_get_tooltip :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    IO CString

{-# DEPRECATED actionGetTooltip ["(Since version 3.10)","Use #GAction instead, and get tooltips from associated","#GtkActionable widgets with gtk_widget_get_tooltip_text()"]#-}
actionGetTooltip ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    m T.Text
actionGetTooltip _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_action_get_tooltip _obj'
    checkUnexpectedReturnNULL "gtk_action_get_tooltip" result
    result' <- cstringToText result
    touchManagedPtr _obj
    return result'

-- method Action::get_visible
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_get_visible" gtk_action_get_visible :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    IO CInt

{-# DEPRECATED actionGetVisible ["(Since version 3.10)","Use #GAction instead, and control and monitor the state of","#GtkActionable widgets directly"]#-}
actionGetVisible ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    m Bool
actionGetVisible _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_action_get_visible _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method Action::get_visible_horizontal
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_get_visible_horizontal" gtk_action_get_visible_horizontal :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    IO CInt

{-# DEPRECATED actionGetVisibleHorizontal ["(Since version 3.10)","Use #GAction instead, and control and monitor the","visibility of associated widgets and menu items directly"]#-}
actionGetVisibleHorizontal ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    m Bool
actionGetVisibleHorizontal _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_action_get_visible_horizontal _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method Action::get_visible_vertical
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_get_visible_vertical" gtk_action_get_visible_vertical :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    IO CInt

{-# DEPRECATED actionGetVisibleVertical ["(Since version 3.10)","Use #GAction instead, and control and monitor the","visibility of associated widgets and menu items directly"]#-}
actionGetVisibleVertical ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    m Bool
actionGetVisibleVertical _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_action_get_visible_vertical _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method Action::is_sensitive
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_is_sensitive" gtk_action_is_sensitive :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    IO CInt

{-# DEPRECATED actionIsSensitive ["(Since version 3.10)","Use g_action_get_enabled() on a #GAction","instead"]#-}
actionIsSensitive ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    m Bool
actionIsSensitive _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_action_is_sensitive _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method Action::is_visible
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_is_visible" gtk_action_is_visible :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    IO CInt

{-# DEPRECATED actionIsVisible ["(Since version 3.10)","Use #GAction instead, and control and monitor the state of","#GtkActionable widgets directly"]#-}
actionIsVisible ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    m Bool
actionIsVisible _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_action_is_visible _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method Action::set_accel_group
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "accel_group", argType = TInterface "Gtk" "AccelGroup", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "accel_group", argType = TInterface "Gtk" "AccelGroup", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_set_accel_group" gtk_action_set_accel_group :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    Ptr AccelGroup ->                       -- accel_group : TInterface "Gtk" "AccelGroup"
    IO ()

{-# DEPRECATED actionSetAccelGroup ["(Since version 3.10)","Use #GAction and the accelerator group on an associated","#GtkMenu instead"]#-}
actionSetAccelGroup ::
    (MonadIO m, ActionK a, AccelGroupK b) =>
    a ->                                    -- _obj
    Maybe (b) ->                            -- accel_group
    m ()
actionSetAccelGroup _obj accel_group = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    maybeAccel_group <- case accel_group of
        Nothing -> return nullPtr
        Just jAccel_group -> do
            let jAccel_group' = unsafeManagedPtrCastPtr jAccel_group
            return jAccel_group'
    gtk_action_set_accel_group _obj' maybeAccel_group
    touchManagedPtr _obj
    whenJust accel_group touchManagedPtr
    return ()

-- method Action::set_accel_path
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "accel_path", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "accel_path", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_set_accel_path" gtk_action_set_accel_path :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    CString ->                              -- accel_path : TBasicType TUTF8
    IO ()

{-# DEPRECATED actionSetAccelPath ["(Since version 3.10)","Use #GAction and the accelerator path on an associated","#GtkMenu instead"]#-}
actionSetAccelPath ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    T.Text ->                               -- accel_path
    m ()
actionSetAccelPath _obj accel_path = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    accel_path' <- textToCString accel_path
    gtk_action_set_accel_path _obj' accel_path'
    touchManagedPtr _obj
    freeMem accel_path'
    return ()

-- method Action::set_always_show_image
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "always_show", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "always_show", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_set_always_show_image" gtk_action_set_always_show_image :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    CInt ->                                 -- always_show : TBasicType TBoolean
    IO ()

{-# DEPRECATED actionSetAlwaysShowImage ["(Since version 3.10)","Use g_menu_item_set_icon() on a #GMenuItem instead, if the","item should have an image"]#-}
actionSetAlwaysShowImage ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- always_show
    m ()
actionSetAlwaysShowImage _obj always_show = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let always_show' = (fromIntegral . fromEnum) always_show
    gtk_action_set_always_show_image _obj' always_show'
    touchManagedPtr _obj
    return ()

-- method Action::set_gicon
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "icon", argType = TInterface "Gio" "Icon", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "icon", argType = TInterface "Gio" "Icon", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_set_gicon" gtk_action_set_gicon :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    Ptr Gio.Icon ->                         -- icon : TInterface "Gio" "Icon"
    IO ()

{-# DEPRECATED actionSetGicon ["(Since version 3.10)","Use #GAction instead, and g_menu_item_set_icon() to set an","icon on a #GMenuItem associated with a #GAction, or gtk_container_add() to","add a #GtkImage to a #GtkButton"]#-}
actionSetGicon ::
    (MonadIO m, ActionK a, Gio.IconK b) =>
    a ->                                    -- _obj
    b ->                                    -- icon
    m ()
actionSetGicon _obj icon = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let icon' = unsafeManagedPtrCastPtr icon
    gtk_action_set_gicon _obj' icon'
    touchManagedPtr _obj
    touchManagedPtr icon
    return ()

-- method Action::set_icon_name
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "icon_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "icon_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_set_icon_name" gtk_action_set_icon_name :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    CString ->                              -- icon_name : TBasicType TUTF8
    IO ()

{-# DEPRECATED actionSetIconName ["(Since version 3.10)","Use #GAction instead, and g_menu_item_set_icon() to set an","icon on a #GMenuItem associated with a #GAction, or gtk_container_add() to","add a #GtkImage to a #GtkButton"]#-}
actionSetIconName ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    T.Text ->                               -- icon_name
    m ()
actionSetIconName _obj icon_name = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    icon_name' <- textToCString icon_name
    gtk_action_set_icon_name _obj' icon_name'
    touchManagedPtr _obj
    freeMem icon_name'
    return ()

-- method Action::set_is_important
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "is_important", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "is_important", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_set_is_important" gtk_action_set_is_important :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    CInt ->                                 -- is_important : TBasicType TBoolean
    IO ()

{-# DEPRECATED actionSetIsImportant ["(Since version 3.10)","Use #GAction instead, and control and monitor whether","labels are shown directly"]#-}
actionSetIsImportant ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- is_important
    m ()
actionSetIsImportant _obj is_important = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let is_important' = (fromIntegral . fromEnum) is_important
    gtk_action_set_is_important _obj' is_important'
    touchManagedPtr _obj
    return ()

-- method Action::set_label
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "label", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "label", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_set_label" gtk_action_set_label :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    CString ->                              -- label : TBasicType TUTF8
    IO ()

{-# DEPRECATED actionSetLabel ["(Since version 3.10)","Use #GAction instead, and set a label on a menu item with","g_menu_item_set_label(). For #GtkActionable widgets, use the widget-specific","API to set a label"]#-}
actionSetLabel ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    T.Text ->                               -- label
    m ()
actionSetLabel _obj label = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    label' <- textToCString label
    gtk_action_set_label _obj' label'
    touchManagedPtr _obj
    freeMem label'
    return ()

-- method Action::set_sensitive
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "sensitive", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "sensitive", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_set_sensitive" gtk_action_set_sensitive :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    CInt ->                                 -- sensitive : TBasicType TBoolean
    IO ()

{-# DEPRECATED actionSetSensitive ["(Since version 3.10)","Use g_simple_action_set_enabled() on a #GSimpleAction","instead"]#-}
actionSetSensitive ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- sensitive
    m ()
actionSetSensitive _obj sensitive = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let sensitive' = (fromIntegral . fromEnum) sensitive
    gtk_action_set_sensitive _obj' sensitive'
    touchManagedPtr _obj
    return ()

-- method Action::set_short_label
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "short_label", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "short_label", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_set_short_label" gtk_action_set_short_label :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    CString ->                              -- short_label : TBasicType TUTF8
    IO ()

{-# DEPRECATED actionSetShortLabel ["(Since version 3.10)","Use #GAction instead, which has no equivalent of short","labels"]#-}
actionSetShortLabel ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    T.Text ->                               -- short_label
    m ()
actionSetShortLabel _obj short_label = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    short_label' <- textToCString short_label
    gtk_action_set_short_label _obj' short_label'
    touchManagedPtr _obj
    freeMem short_label'
    return ()

-- method Action::set_stock_id
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "stock_id", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "stock_id", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_set_stock_id" gtk_action_set_stock_id :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    CString ->                              -- stock_id : TBasicType TUTF8
    IO ()

{-# DEPRECATED actionSetStockId ["(Since version 3.10)","Use #GAction instead, which has no equivalent of stock","items"]#-}
actionSetStockId ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    T.Text ->                               -- stock_id
    m ()
actionSetStockId _obj stock_id = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    stock_id' <- textToCString stock_id
    gtk_action_set_stock_id _obj' stock_id'
    touchManagedPtr _obj
    freeMem stock_id'
    return ()

-- method Action::set_tooltip
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "tooltip", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "tooltip", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_set_tooltip" gtk_action_set_tooltip :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    CString ->                              -- tooltip : TBasicType TUTF8
    IO ()

{-# DEPRECATED actionSetTooltip ["(Since version 3.10)","Use #GAction instead, and set tooltips on associated","#GtkActionable widgets with gtk_widget_set_tooltip_text()"]#-}
actionSetTooltip ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    T.Text ->                               -- tooltip
    m ()
actionSetTooltip _obj tooltip = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    tooltip' <- textToCString tooltip
    gtk_action_set_tooltip _obj' tooltip'
    touchManagedPtr _obj
    freeMem tooltip'
    return ()

-- method Action::set_visible
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "visible", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "visible", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_set_visible" gtk_action_set_visible :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    CInt ->                                 -- visible : TBasicType TBoolean
    IO ()

{-# DEPRECATED actionSetVisible ["(Since version 3.10)","Use #GAction instead, and control and monitor the state of","#GtkActionable widgets directly"]#-}
actionSetVisible ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- visible
    m ()
actionSetVisible _obj visible = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let visible' = (fromIntegral . fromEnum) visible
    gtk_action_set_visible _obj' visible'
    touchManagedPtr _obj
    return ()

-- method Action::set_visible_horizontal
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "visible_horizontal", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "visible_horizontal", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_set_visible_horizontal" gtk_action_set_visible_horizontal :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    CInt ->                                 -- visible_horizontal : TBasicType TBoolean
    IO ()

{-# DEPRECATED actionSetVisibleHorizontal ["(Since version 3.10)","Use #GAction instead, and control and monitor the","visibility of associated widgets and menu items directly"]#-}
actionSetVisibleHorizontal ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- visible_horizontal
    m ()
actionSetVisibleHorizontal _obj visible_horizontal = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let visible_horizontal' = (fromIntegral . fromEnum) visible_horizontal
    gtk_action_set_visible_horizontal _obj' visible_horizontal'
    touchManagedPtr _obj
    return ()

-- method Action::set_visible_vertical
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "visible_vertical", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "visible_vertical", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_set_visible_vertical" gtk_action_set_visible_vertical :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    CInt ->                                 -- visible_vertical : TBasicType TBoolean
    IO ()

{-# DEPRECATED actionSetVisibleVertical ["(Since version 3.10)","Use #GAction instead, and control and monitor the","visibility of associated widgets and menu items directly"]#-}
actionSetVisibleVertical ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- visible_vertical
    m ()
actionSetVisibleVertical _obj visible_vertical = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let visible_vertical' = (fromIntegral . fromEnum) visible_vertical
    gtk_action_set_visible_vertical _obj' visible_vertical'
    touchManagedPtr _obj
    return ()

-- method Action::unblock_activate
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Action", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_action_unblock_activate" gtk_action_unblock_activate :: 
    Ptr Action ->                           -- _obj : TInterface "Gtk" "Action"
    IO ()

{-# DEPRECATED actionUnblockActivate ["(Since version 3.10)","Use g_simple_action_set_enabled() to enable the","#GSimpleAction instead"]#-}
actionUnblockActivate ::
    (MonadIO m, ActionK a) =>
    a ->                                    -- _obj
    m ()
actionUnblockActivate _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    gtk_action_unblock_activate _obj'
    touchManagedPtr _obj
    return ()