{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Objects.Action
(
Action(..) ,
IsAction ,
toAction ,
#if defined(ENABLE_OVERLOADING)
ResolveActionMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
ActionActivateMethodInfo ,
#endif
actionActivate ,
#if defined(ENABLE_OVERLOADING)
ActionBlockActivateMethodInfo ,
#endif
actionBlockActivate ,
#if defined(ENABLE_OVERLOADING)
ActionConnectAcceleratorMethodInfo ,
#endif
actionConnectAccelerator ,
#if defined(ENABLE_OVERLOADING)
ActionCreateIconMethodInfo ,
#endif
actionCreateIcon ,
#if defined(ENABLE_OVERLOADING)
ActionCreateMenuMethodInfo ,
#endif
actionCreateMenu ,
#if defined(ENABLE_OVERLOADING)
ActionCreateMenuItemMethodInfo ,
#endif
actionCreateMenuItem ,
#if defined(ENABLE_OVERLOADING)
ActionCreateToolItemMethodInfo ,
#endif
actionCreateToolItem ,
#if defined(ENABLE_OVERLOADING)
ActionDisconnectAcceleratorMethodInfo ,
#endif
actionDisconnectAccelerator ,
#if defined(ENABLE_OVERLOADING)
ActionGetAccelClosureMethodInfo ,
#endif
actionGetAccelClosure ,
#if defined(ENABLE_OVERLOADING)
ActionGetAccelPathMethodInfo ,
#endif
actionGetAccelPath ,
#if defined(ENABLE_OVERLOADING)
ActionGetAlwaysShowImageMethodInfo ,
#endif
actionGetAlwaysShowImage ,
#if defined(ENABLE_OVERLOADING)
ActionGetGiconMethodInfo ,
#endif
actionGetGicon ,
#if defined(ENABLE_OVERLOADING)
ActionGetIconNameMethodInfo ,
#endif
actionGetIconName ,
#if defined(ENABLE_OVERLOADING)
ActionGetIsImportantMethodInfo ,
#endif
actionGetIsImportant ,
#if defined(ENABLE_OVERLOADING)
ActionGetLabelMethodInfo ,
#endif
actionGetLabel ,
#if defined(ENABLE_OVERLOADING)
ActionGetNameMethodInfo ,
#endif
actionGetName ,
#if defined(ENABLE_OVERLOADING)
ActionGetProxiesMethodInfo ,
#endif
actionGetProxies ,
#if defined(ENABLE_OVERLOADING)
ActionGetSensitiveMethodInfo ,
#endif
actionGetSensitive ,
#if defined(ENABLE_OVERLOADING)
ActionGetShortLabelMethodInfo ,
#endif
actionGetShortLabel ,
#if defined(ENABLE_OVERLOADING)
ActionGetStockIdMethodInfo ,
#endif
actionGetStockId ,
#if defined(ENABLE_OVERLOADING)
ActionGetTooltipMethodInfo ,
#endif
actionGetTooltip ,
#if defined(ENABLE_OVERLOADING)
ActionGetVisibleMethodInfo ,
#endif
actionGetVisible ,
#if defined(ENABLE_OVERLOADING)
ActionGetVisibleHorizontalMethodInfo ,
#endif
actionGetVisibleHorizontal ,
#if defined(ENABLE_OVERLOADING)
ActionGetVisibleVerticalMethodInfo ,
#endif
actionGetVisibleVertical ,
#if defined(ENABLE_OVERLOADING)
ActionIsSensitiveMethodInfo ,
#endif
actionIsSensitive ,
#if defined(ENABLE_OVERLOADING)
ActionIsVisibleMethodInfo ,
#endif
actionIsVisible ,
actionNew ,
#if defined(ENABLE_OVERLOADING)
ActionSetAccelGroupMethodInfo ,
#endif
actionSetAccelGroup ,
#if defined(ENABLE_OVERLOADING)
ActionSetAccelPathMethodInfo ,
#endif
actionSetAccelPath ,
#if defined(ENABLE_OVERLOADING)
ActionSetAlwaysShowImageMethodInfo ,
#endif
actionSetAlwaysShowImage ,
#if defined(ENABLE_OVERLOADING)
ActionSetGiconMethodInfo ,
#endif
actionSetGicon ,
#if defined(ENABLE_OVERLOADING)
ActionSetIconNameMethodInfo ,
#endif
actionSetIconName ,
#if defined(ENABLE_OVERLOADING)
ActionSetIsImportantMethodInfo ,
#endif
actionSetIsImportant ,
#if defined(ENABLE_OVERLOADING)
ActionSetLabelMethodInfo ,
#endif
actionSetLabel ,
#if defined(ENABLE_OVERLOADING)
ActionSetSensitiveMethodInfo ,
#endif
actionSetSensitive ,
#if defined(ENABLE_OVERLOADING)
ActionSetShortLabelMethodInfo ,
#endif
actionSetShortLabel ,
#if defined(ENABLE_OVERLOADING)
ActionSetStockIdMethodInfo ,
#endif
actionSetStockId ,
#if defined(ENABLE_OVERLOADING)
ActionSetTooltipMethodInfo ,
#endif
actionSetTooltip ,
#if defined(ENABLE_OVERLOADING)
ActionSetVisibleMethodInfo ,
#endif
actionSetVisible ,
#if defined(ENABLE_OVERLOADING)
ActionSetVisibleHorizontalMethodInfo ,
#endif
actionSetVisibleHorizontal ,
#if defined(ENABLE_OVERLOADING)
ActionSetVisibleVerticalMethodInfo ,
#endif
actionSetVisibleVertical ,
#if defined(ENABLE_OVERLOADING)
ActionUnblockActivateMethodInfo ,
#endif
actionUnblockActivate ,
#if defined(ENABLE_OVERLOADING)
ActionActionGroupPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
actionActionGroup ,
#endif
clearActionActionGroup ,
constructActionActionGroup ,
getActionActionGroup ,
setActionActionGroup ,
#if defined(ENABLE_OVERLOADING)
ActionAlwaysShowImagePropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
actionAlwaysShowImage ,
#endif
constructActionAlwaysShowImage ,
getActionAlwaysShowImage ,
setActionAlwaysShowImage ,
#if defined(ENABLE_OVERLOADING)
ActionGiconPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
actionGicon ,
#endif
constructActionGicon ,
getActionGicon ,
setActionGicon ,
#if defined(ENABLE_OVERLOADING)
ActionHideIfEmptyPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
actionHideIfEmpty ,
#endif
constructActionHideIfEmpty ,
getActionHideIfEmpty ,
setActionHideIfEmpty ,
#if defined(ENABLE_OVERLOADING)
ActionIconNamePropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
actionIconName ,
#endif
constructActionIconName ,
getActionIconName ,
setActionIconName ,
#if defined(ENABLE_OVERLOADING)
ActionIsImportantPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
actionIsImportant ,
#endif
constructActionIsImportant ,
getActionIsImportant ,
setActionIsImportant ,
#if defined(ENABLE_OVERLOADING)
ActionLabelPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
actionLabel ,
#endif
constructActionLabel ,
getActionLabel ,
setActionLabel ,
#if defined(ENABLE_OVERLOADING)
ActionNamePropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
actionName ,
#endif
constructActionName ,
getActionName ,
#if defined(ENABLE_OVERLOADING)
ActionSensitivePropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
actionSensitive ,
#endif
constructActionSensitive ,
getActionSensitive ,
setActionSensitive ,
#if defined(ENABLE_OVERLOADING)
ActionShortLabelPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
actionShortLabel ,
#endif
constructActionShortLabel ,
getActionShortLabel ,
setActionShortLabel ,
#if defined(ENABLE_OVERLOADING)
ActionStockIdPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
actionStockId ,
#endif
constructActionStockId ,
getActionStockId ,
setActionStockId ,
#if defined(ENABLE_OVERLOADING)
ActionTooltipPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
actionTooltip ,
#endif
constructActionTooltip ,
getActionTooltip ,
setActionTooltip ,
#if defined(ENABLE_OVERLOADING)
ActionVisiblePropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
actionVisible ,
#endif
constructActionVisible ,
getActionVisible ,
setActionVisible ,
#if defined(ENABLE_OVERLOADING)
ActionVisibleHorizontalPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
actionVisibleHorizontal ,
#endif
constructActionVisibleHorizontal ,
getActionVisibleHorizontal ,
setActionVisibleHorizontal ,
#if defined(ENABLE_OVERLOADING)
ActionVisibleOverflownPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
actionVisibleOverflown ,
#endif
constructActionVisibleOverflown ,
getActionVisibleOverflown ,
setActionVisibleOverflown ,
#if defined(ENABLE_OVERLOADING)
ActionVisibleVerticalPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
actionVisibleVertical ,
#endif
constructActionVisibleVertical ,
getActionVisibleVertical ,
setActionVisibleVertical ,
ActionActivateCallback ,
#if defined(ENABLE_OVERLOADING)
ActionActivateSignalInfo ,
#endif
C_ActionActivateCallback ,
afterActionActivate ,
genClosure_ActionActivate ,
mk_ActionActivateCallback ,
noActionActivateCallback ,
onActionActivate ,
wrap_ActionActivateCallback ,
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Interfaces.Icon as Gio.Icon
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Objects.AccelGroup as Gtk.AccelGroup
import {-# SOURCE #-} qualified GI.Gtk.Objects.ActionGroup as Gtk.ActionGroup
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget
newtype Action = Action (SP.ManagedPtr Action)
deriving (Action -> Action -> Bool
(Action -> Action -> Bool)
-> (Action -> Action -> Bool) -> Eq Action
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Action -> Action -> Bool
$c/= :: Action -> Action -> Bool
== :: Action -> Action -> Bool
$c== :: Action -> Action -> Bool
Eq)
instance SP.ManagedPtrNewtype Action where
toManagedPtr :: Action -> ManagedPtr Action
toManagedPtr (Action ManagedPtr Action
p) = ManagedPtr Action
p
foreign import ccall "gtk_action_get_type"
c_gtk_action_get_type :: IO B.Types.GType
instance B.Types.TypedObject Action where
glibType :: IO GType
glibType = IO GType
c_gtk_action_get_type
instance B.Types.GObject Action
instance B.GValue.IsGValue Action where
toGValue :: Action -> IO GValue
toGValue Action
o = do
GType
gtype <- IO GType
c_gtk_action_get_type
Action -> (Ptr Action -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Action
o (GType -> (GValue -> Ptr Action -> IO ()) -> Ptr Action -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr Action -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO Action
fromGValue GValue
gv = do
Ptr Action
ptr <- GValue -> IO (Ptr Action)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr Action)
(ManagedPtr Action -> Action) -> Ptr Action -> IO Action
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Action -> Action
Action Ptr Action
ptr
class (SP.GObject o, O.IsDescendantOf Action o) => IsAction o
instance (SP.GObject o, O.IsDescendantOf Action o) => IsAction o
instance O.HasParentTypes Action
type instance O.ParentTypes Action = '[GObject.Object.Object, Gtk.Buildable.Buildable]
toAction :: (MonadIO m, IsAction o) => o -> m Action
toAction :: o -> m Action
toAction = IO Action -> m Action
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Action -> m Action) -> (o -> IO Action) -> o -> m Action
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Action -> Action) -> o -> IO Action
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr Action -> Action
Action
#if defined(ENABLE_OVERLOADING)
type family ResolveActionMethod (t :: Symbol) (o :: *) :: * where
ResolveActionMethod "activate" o = ActionActivateMethodInfo
ResolveActionMethod "addChild" o = Gtk.Buildable.BuildableAddChildMethodInfo
ResolveActionMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveActionMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveActionMethod "blockActivate" o = ActionBlockActivateMethodInfo
ResolveActionMethod "connectAccelerator" o = ActionConnectAcceleratorMethodInfo
ResolveActionMethod "constructChild" o = Gtk.Buildable.BuildableConstructChildMethodInfo
ResolveActionMethod "createIcon" o = ActionCreateIconMethodInfo
ResolveActionMethod "createMenu" o = ActionCreateMenuMethodInfo
ResolveActionMethod "createMenuItem" o = ActionCreateMenuItemMethodInfo
ResolveActionMethod "createToolItem" o = ActionCreateToolItemMethodInfo
ResolveActionMethod "customFinished" o = Gtk.Buildable.BuildableCustomFinishedMethodInfo
ResolveActionMethod "customTagEnd" o = Gtk.Buildable.BuildableCustomTagEndMethodInfo
ResolveActionMethod "customTagStart" o = Gtk.Buildable.BuildableCustomTagStartMethodInfo
ResolveActionMethod "disconnectAccelerator" o = ActionDisconnectAcceleratorMethodInfo
ResolveActionMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveActionMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveActionMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveActionMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveActionMethod "isSensitive" o = ActionIsSensitiveMethodInfo
ResolveActionMethod "isVisible" o = ActionIsVisibleMethodInfo
ResolveActionMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveActionMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveActionMethod "parserFinished" o = Gtk.Buildable.BuildableParserFinishedMethodInfo
ResolveActionMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveActionMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveActionMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveActionMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveActionMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveActionMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveActionMethod "unblockActivate" o = ActionUnblockActivateMethodInfo
ResolveActionMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveActionMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveActionMethod "getAccelClosure" o = ActionGetAccelClosureMethodInfo
ResolveActionMethod "getAccelPath" o = ActionGetAccelPathMethodInfo
ResolveActionMethod "getAlwaysShowImage" o = ActionGetAlwaysShowImageMethodInfo
ResolveActionMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveActionMethod "getGicon" o = ActionGetGiconMethodInfo
ResolveActionMethod "getIconName" o = ActionGetIconNameMethodInfo
ResolveActionMethod "getInternalChild" o = Gtk.Buildable.BuildableGetInternalChildMethodInfo
ResolveActionMethod "getIsImportant" o = ActionGetIsImportantMethodInfo
ResolveActionMethod "getLabel" o = ActionGetLabelMethodInfo
ResolveActionMethod "getName" o = ActionGetNameMethodInfo
ResolveActionMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveActionMethod "getProxies" o = ActionGetProxiesMethodInfo
ResolveActionMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveActionMethod "getSensitive" o = ActionGetSensitiveMethodInfo
ResolveActionMethod "getShortLabel" o = ActionGetShortLabelMethodInfo
ResolveActionMethod "getStockId" o = ActionGetStockIdMethodInfo
ResolveActionMethod "getTooltip" o = ActionGetTooltipMethodInfo
ResolveActionMethod "getVisible" o = ActionGetVisibleMethodInfo
ResolveActionMethod "getVisibleHorizontal" o = ActionGetVisibleHorizontalMethodInfo
ResolveActionMethod "getVisibleVertical" o = ActionGetVisibleVerticalMethodInfo
ResolveActionMethod "setAccelGroup" o = ActionSetAccelGroupMethodInfo
ResolveActionMethod "setAccelPath" o = ActionSetAccelPathMethodInfo
ResolveActionMethod "setAlwaysShowImage" o = ActionSetAlwaysShowImageMethodInfo
ResolveActionMethod "setBuildableProperty" o = Gtk.Buildable.BuildableSetBuildablePropertyMethodInfo
ResolveActionMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveActionMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveActionMethod "setGicon" o = ActionSetGiconMethodInfo
ResolveActionMethod "setIconName" o = ActionSetIconNameMethodInfo
ResolveActionMethod "setIsImportant" o = ActionSetIsImportantMethodInfo
ResolveActionMethod "setLabel" o = ActionSetLabelMethodInfo
ResolveActionMethod "setName" o = Gtk.Buildable.BuildableSetNameMethodInfo
ResolveActionMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveActionMethod "setSensitive" o = ActionSetSensitiveMethodInfo
ResolveActionMethod "setShortLabel" o = ActionSetShortLabelMethodInfo
ResolveActionMethod "setStockId" o = ActionSetStockIdMethodInfo
ResolveActionMethod "setTooltip" o = ActionSetTooltipMethodInfo
ResolveActionMethod "setVisible" o = ActionSetVisibleMethodInfo
ResolveActionMethod "setVisibleHorizontal" o = ActionSetVisibleHorizontalMethodInfo
ResolveActionMethod "setVisibleVertical" o = ActionSetVisibleVerticalMethodInfo
ResolveActionMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveActionMethod t Action, O.MethodInfo info Action p) => OL.IsLabel t (Action -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
{-# DEPRECATED ActionActivateCallback ["(Since version 3.10)","Use [activate](\"GI.Gio.Objects.SimpleAction#g:signal:activate\") instead"] #-}
type ActionActivateCallback =
IO ()
noActionActivateCallback :: Maybe ActionActivateCallback
noActionActivateCallback :: Maybe (IO ())
noActionActivateCallback = Maybe (IO ())
forall a. Maybe a
Nothing
type C_ActionActivateCallback =
Ptr () ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_ActionActivateCallback :: C_ActionActivateCallback -> IO (FunPtr C_ActionActivateCallback)
genClosure_ActionActivate :: MonadIO m => ActionActivateCallback -> m (GClosure C_ActionActivateCallback)
genClosure_ActionActivate :: IO () -> m (GClosure C_ActionActivateCallback)
genClosure_ActionActivate IO ()
cb = IO (GClosure C_ActionActivateCallback)
-> m (GClosure C_ActionActivateCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_ActionActivateCallback)
-> m (GClosure C_ActionActivateCallback))
-> IO (GClosure C_ActionActivateCallback)
-> m (GClosure C_ActionActivateCallback)
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_ActionActivateCallback
cb' = IO () -> C_ActionActivateCallback
wrap_ActionActivateCallback IO ()
cb
C_ActionActivateCallback -> IO (FunPtr C_ActionActivateCallback)
mk_ActionActivateCallback C_ActionActivateCallback
cb' IO (FunPtr C_ActionActivateCallback)
-> (FunPtr C_ActionActivateCallback
-> IO (GClosure C_ActionActivateCallback))
-> IO (GClosure C_ActionActivateCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_ActionActivateCallback
-> IO (GClosure C_ActionActivateCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_ActionActivateCallback ::
ActionActivateCallback ->
C_ActionActivateCallback
wrap_ActionActivateCallback :: IO () -> C_ActionActivateCallback
wrap_ActionActivateCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
IO ()
_cb
onActionActivate :: (IsAction a, MonadIO m) => a -> ActionActivateCallback -> m SignalHandlerId
onActionActivate :: a -> IO () -> m SignalHandlerId
onActionActivate a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_ActionActivateCallback
cb' = IO () -> C_ActionActivateCallback
wrap_ActionActivateCallback IO ()
cb
FunPtr C_ActionActivateCallback
cb'' <- C_ActionActivateCallback -> IO (FunPtr C_ActionActivateCallback)
mk_ActionActivateCallback C_ActionActivateCallback
cb'
a
-> Text
-> FunPtr C_ActionActivateCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"activate" FunPtr C_ActionActivateCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterActionActivate :: (IsAction a, MonadIO m) => a -> ActionActivateCallback -> m SignalHandlerId
afterActionActivate :: a -> IO () -> m SignalHandlerId
afterActionActivate a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_ActionActivateCallback
cb' = IO () -> C_ActionActivateCallback
wrap_ActionActivateCallback IO ()
cb
FunPtr C_ActionActivateCallback
cb'' <- C_ActionActivateCallback -> IO (FunPtr C_ActionActivateCallback)
mk_ActionActivateCallback C_ActionActivateCallback
cb'
a
-> Text
-> FunPtr C_ActionActivateCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"activate" FunPtr C_ActionActivateCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data ActionActivateSignalInfo
instance SignalInfo ActionActivateSignalInfo where
type HaskellCallbackType ActionActivateSignalInfo = ActionActivateCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_ActionActivateCallback cb
cb'' <- mk_ActionActivateCallback cb'
connectSignalFunPtr obj "activate" cb'' connectMode detail
#endif
getActionActionGroup :: (MonadIO m, IsAction o) => o -> m (Maybe Gtk.ActionGroup.ActionGroup)
getActionActionGroup :: o -> m (Maybe ActionGroup)
getActionActionGroup o
obj = IO (Maybe ActionGroup) -> m (Maybe ActionGroup)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe ActionGroup) -> m (Maybe ActionGroup))
-> IO (Maybe ActionGroup) -> m (Maybe ActionGroup)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr ActionGroup -> ActionGroup)
-> IO (Maybe ActionGroup)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"action-group" ManagedPtr ActionGroup -> ActionGroup
Gtk.ActionGroup.ActionGroup
setActionActionGroup :: (MonadIO m, IsAction o, Gtk.ActionGroup.IsActionGroup a) => o -> a -> m ()
setActionActionGroup :: o -> a -> m ()
setActionActionGroup o
obj a
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"action-group" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructActionActionGroup :: (IsAction o, MIO.MonadIO m, Gtk.ActionGroup.IsActionGroup a) => a -> m (GValueConstruct o)
constructActionActionGroup :: a -> m (GValueConstruct o)
constructActionActionGroup a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"action-group" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
clearActionActionGroup :: (MonadIO m, IsAction o) => o -> m ()
clearActionActionGroup :: o -> m ()
clearActionActionGroup 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 ActionGroup -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"action-group" (Maybe ActionGroup
forall a. Maybe a
Nothing :: Maybe Gtk.ActionGroup.ActionGroup)
#if defined(ENABLE_OVERLOADING)
data ActionActionGroupPropertyInfo
instance AttrInfo ActionActionGroupPropertyInfo where
type AttrAllowedOps ActionActionGroupPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint ActionActionGroupPropertyInfo = IsAction
type AttrSetTypeConstraint ActionActionGroupPropertyInfo = Gtk.ActionGroup.IsActionGroup
type AttrTransferTypeConstraint ActionActionGroupPropertyInfo = Gtk.ActionGroup.IsActionGroup
type AttrTransferType ActionActionGroupPropertyInfo = Gtk.ActionGroup.ActionGroup
type AttrGetType ActionActionGroupPropertyInfo = (Maybe Gtk.ActionGroup.ActionGroup)
type AttrLabel ActionActionGroupPropertyInfo = "action-group"
type AttrOrigin ActionActionGroupPropertyInfo = Action
attrGet = getActionActionGroup
attrSet = setActionActionGroup
attrTransfer _ v = do
unsafeCastTo Gtk.ActionGroup.ActionGroup v
attrConstruct = constructActionActionGroup
attrClear = clearActionActionGroup
#endif
getActionAlwaysShowImage :: (MonadIO m, IsAction o) => o -> m Bool
getActionAlwaysShowImage :: o -> m Bool
getActionAlwaysShowImage o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"always-show-image"
setActionAlwaysShowImage :: (MonadIO m, IsAction o) => o -> Bool -> m ()
setActionAlwaysShowImage :: o -> Bool -> m ()
setActionAlwaysShowImage o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"always-show-image" Bool
val
constructActionAlwaysShowImage :: (IsAction o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructActionAlwaysShowImage :: Bool -> m (GValueConstruct o)
constructActionAlwaysShowImage Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"always-show-image" Bool
val
#if defined(ENABLE_OVERLOADING)
data ActionAlwaysShowImagePropertyInfo
instance AttrInfo ActionAlwaysShowImagePropertyInfo where
type AttrAllowedOps ActionAlwaysShowImagePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint ActionAlwaysShowImagePropertyInfo = IsAction
type AttrSetTypeConstraint ActionAlwaysShowImagePropertyInfo = (~) Bool
type AttrTransferTypeConstraint ActionAlwaysShowImagePropertyInfo = (~) Bool
type AttrTransferType ActionAlwaysShowImagePropertyInfo = Bool
type AttrGetType ActionAlwaysShowImagePropertyInfo = Bool
type AttrLabel ActionAlwaysShowImagePropertyInfo = "always-show-image"
type AttrOrigin ActionAlwaysShowImagePropertyInfo = Action
attrGet = getActionAlwaysShowImage
attrSet = setActionAlwaysShowImage
attrTransfer _ v = do
return v
attrConstruct = constructActionAlwaysShowImage
attrClear = undefined
#endif
getActionGicon :: (MonadIO m, IsAction o) => o -> m Gio.Icon.Icon
getActionGicon :: o -> m Icon
getActionGicon o
obj = IO Icon -> m Icon
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Icon -> m Icon) -> IO Icon -> m Icon
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Icon) -> IO Icon
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getActionGicon" (IO (Maybe Icon) -> IO Icon) -> IO (Maybe Icon) -> IO Icon
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr Icon -> Icon) -> IO (Maybe Icon)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"gicon" ManagedPtr Icon -> Icon
Gio.Icon.Icon
setActionGicon :: (MonadIO m, IsAction o, Gio.Icon.IsIcon a) => o -> a -> m ()
setActionGicon :: o -> a -> m ()
setActionGicon o
obj a
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"gicon" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructActionGicon :: (IsAction o, MIO.MonadIO m, Gio.Icon.IsIcon a) => a -> m (GValueConstruct o)
constructActionGicon :: a -> m (GValueConstruct o)
constructActionGicon a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"gicon" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
#if defined(ENABLE_OVERLOADING)
data ActionGiconPropertyInfo
instance AttrInfo ActionGiconPropertyInfo where
type AttrAllowedOps ActionGiconPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint ActionGiconPropertyInfo = IsAction
type AttrSetTypeConstraint ActionGiconPropertyInfo = Gio.Icon.IsIcon
type AttrTransferTypeConstraint ActionGiconPropertyInfo = Gio.Icon.IsIcon
type AttrTransferType ActionGiconPropertyInfo = Gio.Icon.Icon
type AttrGetType ActionGiconPropertyInfo = Gio.Icon.Icon
type AttrLabel ActionGiconPropertyInfo = "gicon"
type AttrOrigin ActionGiconPropertyInfo = Action
attrGet = getActionGicon
attrSet = setActionGicon
attrTransfer _ v = do
unsafeCastTo Gio.Icon.Icon v
attrConstruct = constructActionGicon
attrClear = undefined
#endif
getActionHideIfEmpty :: (MonadIO m, IsAction o) => o -> m Bool
getActionHideIfEmpty :: o -> m Bool
getActionHideIfEmpty o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"hide-if-empty"
setActionHideIfEmpty :: (MonadIO m, IsAction o) => o -> Bool -> m ()
setActionHideIfEmpty :: o -> Bool -> m ()
setActionHideIfEmpty o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"hide-if-empty" Bool
val
constructActionHideIfEmpty :: (IsAction o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructActionHideIfEmpty :: Bool -> m (GValueConstruct o)
constructActionHideIfEmpty Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"hide-if-empty" Bool
val
#if defined(ENABLE_OVERLOADING)
data ActionHideIfEmptyPropertyInfo
instance AttrInfo ActionHideIfEmptyPropertyInfo where
type AttrAllowedOps ActionHideIfEmptyPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint ActionHideIfEmptyPropertyInfo = IsAction
type AttrSetTypeConstraint ActionHideIfEmptyPropertyInfo = (~) Bool
type AttrTransferTypeConstraint ActionHideIfEmptyPropertyInfo = (~) Bool
type AttrTransferType ActionHideIfEmptyPropertyInfo = Bool
type AttrGetType ActionHideIfEmptyPropertyInfo = Bool
type AttrLabel ActionHideIfEmptyPropertyInfo = "hide-if-empty"
type AttrOrigin ActionHideIfEmptyPropertyInfo = Action
attrGet = getActionHideIfEmpty
attrSet = setActionHideIfEmpty
attrTransfer _ v = do
return v
attrConstruct = constructActionHideIfEmpty
attrClear = undefined
#endif
getActionIconName :: (MonadIO m, IsAction o) => o -> m T.Text
getActionIconName :: o -> m Text
getActionIconName o
obj = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getActionIconName" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"icon-name"
setActionIconName :: (MonadIO m, IsAction o) => o -> T.Text -> m ()
setActionIconName :: o -> Text -> m ()
setActionIconName o
obj Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"icon-name" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructActionIconName :: (IsAction o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructActionIconName :: Text -> m (GValueConstruct o)
constructActionIconName Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"icon-name" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data ActionIconNamePropertyInfo
instance AttrInfo ActionIconNamePropertyInfo where
type AttrAllowedOps ActionIconNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint ActionIconNamePropertyInfo = IsAction
type AttrSetTypeConstraint ActionIconNamePropertyInfo = (~) T.Text
type AttrTransferTypeConstraint ActionIconNamePropertyInfo = (~) T.Text
type AttrTransferType ActionIconNamePropertyInfo = T.Text
type AttrGetType ActionIconNamePropertyInfo = T.Text
type AttrLabel ActionIconNamePropertyInfo = "icon-name"
type AttrOrigin ActionIconNamePropertyInfo = Action
attrGet = getActionIconName
attrSet = setActionIconName
attrTransfer _ v = do
return v
attrConstruct = constructActionIconName
attrClear = undefined
#endif
getActionIsImportant :: (MonadIO m, IsAction o) => o -> m Bool
getActionIsImportant :: o -> m Bool
getActionIsImportant o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"is-important"
setActionIsImportant :: (MonadIO m, IsAction o) => o -> Bool -> m ()
setActionIsImportant :: o -> Bool -> m ()
setActionIsImportant o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"is-important" Bool
val
constructActionIsImportant :: (IsAction o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructActionIsImportant :: Bool -> m (GValueConstruct o)
constructActionIsImportant Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"is-important" Bool
val
#if defined(ENABLE_OVERLOADING)
data ActionIsImportantPropertyInfo
instance AttrInfo ActionIsImportantPropertyInfo where
type AttrAllowedOps ActionIsImportantPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint ActionIsImportantPropertyInfo = IsAction
type AttrSetTypeConstraint ActionIsImportantPropertyInfo = (~) Bool
type AttrTransferTypeConstraint ActionIsImportantPropertyInfo = (~) Bool
type AttrTransferType ActionIsImportantPropertyInfo = Bool
type AttrGetType ActionIsImportantPropertyInfo = Bool
type AttrLabel ActionIsImportantPropertyInfo = "is-important"
type AttrOrigin ActionIsImportantPropertyInfo = Action
attrGet = getActionIsImportant
attrSet = setActionIsImportant
attrTransfer _ v = do
return v
attrConstruct = constructActionIsImportant
attrClear = undefined
#endif
getActionLabel :: (MonadIO m, IsAction o) => o -> m T.Text
getActionLabel :: o -> m Text
getActionLabel o
obj = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getActionLabel" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"label"
setActionLabel :: (MonadIO m, IsAction o) => o -> T.Text -> m ()
setActionLabel :: o -> Text -> m ()
setActionLabel o
obj Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"label" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructActionLabel :: (IsAction o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructActionLabel :: Text -> m (GValueConstruct o)
constructActionLabel Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"label" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data ActionLabelPropertyInfo
instance AttrInfo ActionLabelPropertyInfo where
type AttrAllowedOps ActionLabelPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint ActionLabelPropertyInfo = IsAction
type AttrSetTypeConstraint ActionLabelPropertyInfo = (~) T.Text
type AttrTransferTypeConstraint ActionLabelPropertyInfo = (~) T.Text
type AttrTransferType ActionLabelPropertyInfo = T.Text
type AttrGetType ActionLabelPropertyInfo = T.Text
type AttrLabel ActionLabelPropertyInfo = "label"
type AttrOrigin ActionLabelPropertyInfo = Action
attrGet = getActionLabel
attrSet = setActionLabel
attrTransfer _ v = do
return v
attrConstruct = constructActionLabel
attrClear = undefined
#endif
getActionName :: (MonadIO m, IsAction o) => o -> m T.Text
getActionName :: o -> m Text
getActionName o
obj = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getActionName" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"name"
constructActionName :: (IsAction o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructActionName :: Text -> m (GValueConstruct o)
constructActionName Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"name" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data ActionNamePropertyInfo
instance AttrInfo ActionNamePropertyInfo where
type AttrAllowedOps ActionNamePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint ActionNamePropertyInfo = IsAction
type AttrSetTypeConstraint ActionNamePropertyInfo = (~) T.Text
type AttrTransferTypeConstraint ActionNamePropertyInfo = (~) T.Text
type AttrTransferType ActionNamePropertyInfo = T.Text
type AttrGetType ActionNamePropertyInfo = T.Text
type AttrLabel ActionNamePropertyInfo = "name"
type AttrOrigin ActionNamePropertyInfo = Action
attrGet = getActionName
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructActionName
attrClear = undefined
#endif
getActionSensitive :: (MonadIO m, IsAction o) => o -> m Bool
getActionSensitive :: o -> m Bool
getActionSensitive o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"sensitive"
setActionSensitive :: (MonadIO m, IsAction o) => o -> Bool -> m ()
setActionSensitive :: o -> Bool -> m ()
setActionSensitive o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"sensitive" Bool
val
constructActionSensitive :: (IsAction o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructActionSensitive :: Bool -> m (GValueConstruct o)
constructActionSensitive Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"sensitive" Bool
val
#if defined(ENABLE_OVERLOADING)
data ActionSensitivePropertyInfo
instance AttrInfo ActionSensitivePropertyInfo where
type AttrAllowedOps ActionSensitivePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint ActionSensitivePropertyInfo = IsAction
type AttrSetTypeConstraint ActionSensitivePropertyInfo = (~) Bool
type AttrTransferTypeConstraint ActionSensitivePropertyInfo = (~) Bool
type AttrTransferType ActionSensitivePropertyInfo = Bool
type AttrGetType ActionSensitivePropertyInfo = Bool
type AttrLabel ActionSensitivePropertyInfo = "sensitive"
type AttrOrigin ActionSensitivePropertyInfo = Action
attrGet = getActionSensitive
attrSet = setActionSensitive
attrTransfer _ v = do
return v
attrConstruct = constructActionSensitive
attrClear = undefined
#endif
getActionShortLabel :: (MonadIO m, IsAction o) => o -> m T.Text
getActionShortLabel :: o -> m Text
getActionShortLabel o
obj = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getActionShortLabel" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"short-label"
setActionShortLabel :: (MonadIO m, IsAction o) => o -> T.Text -> m ()
setActionShortLabel :: o -> Text -> m ()
setActionShortLabel o
obj Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"short-label" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructActionShortLabel :: (IsAction o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructActionShortLabel :: Text -> m (GValueConstruct o)
constructActionShortLabel Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"short-label" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data ActionShortLabelPropertyInfo
instance AttrInfo ActionShortLabelPropertyInfo where
type AttrAllowedOps ActionShortLabelPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint ActionShortLabelPropertyInfo = IsAction
type AttrSetTypeConstraint ActionShortLabelPropertyInfo = (~) T.Text
type AttrTransferTypeConstraint ActionShortLabelPropertyInfo = (~) T.Text
type AttrTransferType ActionShortLabelPropertyInfo = T.Text
type AttrGetType ActionShortLabelPropertyInfo = T.Text
type AttrLabel ActionShortLabelPropertyInfo = "short-label"
type AttrOrigin ActionShortLabelPropertyInfo = Action
attrGet = getActionShortLabel
attrSet = setActionShortLabel
attrTransfer _ v = do
return v
attrConstruct = constructActionShortLabel
attrClear = undefined
#endif
getActionStockId :: (MonadIO m, IsAction o) => o -> m T.Text
getActionStockId :: o -> m Text
getActionStockId o
obj = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getActionStockId" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"stock-id"
setActionStockId :: (MonadIO m, IsAction o) => o -> T.Text -> m ()
setActionStockId :: o -> Text -> m ()
setActionStockId o
obj Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"stock-id" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructActionStockId :: (IsAction o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructActionStockId :: Text -> m (GValueConstruct o)
constructActionStockId Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"stock-id" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data ActionStockIdPropertyInfo
instance AttrInfo ActionStockIdPropertyInfo where
type AttrAllowedOps ActionStockIdPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint ActionStockIdPropertyInfo = IsAction
type AttrSetTypeConstraint ActionStockIdPropertyInfo = (~) T.Text
type AttrTransferTypeConstraint ActionStockIdPropertyInfo = (~) T.Text
type AttrTransferType ActionStockIdPropertyInfo = T.Text
type AttrGetType ActionStockIdPropertyInfo = T.Text
type AttrLabel ActionStockIdPropertyInfo = "stock-id"
type AttrOrigin ActionStockIdPropertyInfo = Action
attrGet = getActionStockId
attrSet = setActionStockId
attrTransfer _ v = do
return v
attrConstruct = constructActionStockId
attrClear = undefined
#endif
getActionTooltip :: (MonadIO m, IsAction o) => o -> m T.Text
getActionTooltip :: o -> m Text
getActionTooltip o
obj = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getActionTooltip" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"tooltip"
setActionTooltip :: (MonadIO m, IsAction o) => o -> T.Text -> m ()
setActionTooltip :: o -> Text -> m ()
setActionTooltip o
obj Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"tooltip" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructActionTooltip :: (IsAction o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructActionTooltip :: Text -> m (GValueConstruct o)
constructActionTooltip Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"tooltip" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data ActionTooltipPropertyInfo
instance AttrInfo ActionTooltipPropertyInfo where
type AttrAllowedOps ActionTooltipPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint ActionTooltipPropertyInfo = IsAction
type AttrSetTypeConstraint ActionTooltipPropertyInfo = (~) T.Text
type AttrTransferTypeConstraint ActionTooltipPropertyInfo = (~) T.Text
type AttrTransferType ActionTooltipPropertyInfo = T.Text
type AttrGetType ActionTooltipPropertyInfo = T.Text
type AttrLabel ActionTooltipPropertyInfo = "tooltip"
type AttrOrigin ActionTooltipPropertyInfo = Action
attrGet = getActionTooltip
attrSet = setActionTooltip
attrTransfer _ v = do
return v
attrConstruct = constructActionTooltip
attrClear = undefined
#endif
getActionVisible :: (MonadIO m, IsAction o) => o -> m Bool
getActionVisible :: o -> m Bool
getActionVisible o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"visible"
setActionVisible :: (MonadIO m, IsAction o) => o -> Bool -> m ()
setActionVisible :: o -> Bool -> m ()
setActionVisible o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"visible" Bool
val
constructActionVisible :: (IsAction o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructActionVisible :: Bool -> m (GValueConstruct o)
constructActionVisible Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"visible" Bool
val
#if defined(ENABLE_OVERLOADING)
data ActionVisiblePropertyInfo
instance AttrInfo ActionVisiblePropertyInfo where
type AttrAllowedOps ActionVisiblePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint ActionVisiblePropertyInfo = IsAction
type AttrSetTypeConstraint ActionVisiblePropertyInfo = (~) Bool
type AttrTransferTypeConstraint ActionVisiblePropertyInfo = (~) Bool
type AttrTransferType ActionVisiblePropertyInfo = Bool
type AttrGetType ActionVisiblePropertyInfo = Bool
type AttrLabel ActionVisiblePropertyInfo = "visible"
type AttrOrigin ActionVisiblePropertyInfo = Action
attrGet = getActionVisible
attrSet = setActionVisible
attrTransfer _ v = do
return v
attrConstruct = constructActionVisible
attrClear = undefined
#endif
getActionVisibleHorizontal :: (MonadIO m, IsAction o) => o -> m Bool
getActionVisibleHorizontal :: o -> m Bool
getActionVisibleHorizontal o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"visible-horizontal"
setActionVisibleHorizontal :: (MonadIO m, IsAction o) => o -> Bool -> m ()
setActionVisibleHorizontal :: o -> Bool -> m ()
setActionVisibleHorizontal o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"visible-horizontal" Bool
val
constructActionVisibleHorizontal :: (IsAction o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructActionVisibleHorizontal :: Bool -> m (GValueConstruct o)
constructActionVisibleHorizontal Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"visible-horizontal" Bool
val
#if defined(ENABLE_OVERLOADING)
data ActionVisibleHorizontalPropertyInfo
instance AttrInfo ActionVisibleHorizontalPropertyInfo where
type AttrAllowedOps ActionVisibleHorizontalPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint ActionVisibleHorizontalPropertyInfo = IsAction
type AttrSetTypeConstraint ActionVisibleHorizontalPropertyInfo = (~) Bool
type AttrTransferTypeConstraint ActionVisibleHorizontalPropertyInfo = (~) Bool
type AttrTransferType ActionVisibleHorizontalPropertyInfo = Bool
type AttrGetType ActionVisibleHorizontalPropertyInfo = Bool
type AttrLabel ActionVisibleHorizontalPropertyInfo = "visible-horizontal"
type AttrOrigin ActionVisibleHorizontalPropertyInfo = Action
attrGet = getActionVisibleHorizontal
attrSet = setActionVisibleHorizontal
attrTransfer _ v = do
return v
attrConstruct = constructActionVisibleHorizontal
attrClear = undefined
#endif
getActionVisibleOverflown :: (MonadIO m, IsAction o) => o -> m Bool
getActionVisibleOverflown :: o -> m Bool
getActionVisibleOverflown o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"visible-overflown"
setActionVisibleOverflown :: (MonadIO m, IsAction o) => o -> Bool -> m ()
setActionVisibleOverflown :: o -> Bool -> m ()
setActionVisibleOverflown o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"visible-overflown" Bool
val
constructActionVisibleOverflown :: (IsAction o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructActionVisibleOverflown :: Bool -> m (GValueConstruct o)
constructActionVisibleOverflown Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"visible-overflown" Bool
val
#if defined(ENABLE_OVERLOADING)
data ActionVisibleOverflownPropertyInfo
instance AttrInfo ActionVisibleOverflownPropertyInfo where
type AttrAllowedOps ActionVisibleOverflownPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint ActionVisibleOverflownPropertyInfo = IsAction
type AttrSetTypeConstraint ActionVisibleOverflownPropertyInfo = (~) Bool
type AttrTransferTypeConstraint ActionVisibleOverflownPropertyInfo = (~) Bool
type AttrTransferType ActionVisibleOverflownPropertyInfo = Bool
type AttrGetType ActionVisibleOverflownPropertyInfo = Bool
type AttrLabel ActionVisibleOverflownPropertyInfo = "visible-overflown"
type AttrOrigin ActionVisibleOverflownPropertyInfo = Action
attrGet = getActionVisibleOverflown
attrSet = setActionVisibleOverflown
attrTransfer _ v = do
return v
attrConstruct = constructActionVisibleOverflown
attrClear = undefined
#endif
getActionVisibleVertical :: (MonadIO m, IsAction o) => o -> m Bool
getActionVisibleVertical :: o -> m Bool
getActionVisibleVertical o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"visible-vertical"
setActionVisibleVertical :: (MonadIO m, IsAction o) => o -> Bool -> m ()
setActionVisibleVertical :: o -> Bool -> m ()
setActionVisibleVertical o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"visible-vertical" Bool
val
constructActionVisibleVertical :: (IsAction o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructActionVisibleVertical :: Bool -> m (GValueConstruct o)
constructActionVisibleVertical Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"visible-vertical" Bool
val
#if defined(ENABLE_OVERLOADING)
data ActionVisibleVerticalPropertyInfo
instance AttrInfo ActionVisibleVerticalPropertyInfo where
type AttrAllowedOps ActionVisibleVerticalPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint ActionVisibleVerticalPropertyInfo = IsAction
type AttrSetTypeConstraint ActionVisibleVerticalPropertyInfo = (~) Bool
type AttrTransferTypeConstraint ActionVisibleVerticalPropertyInfo = (~) Bool
type AttrTransferType ActionVisibleVerticalPropertyInfo = Bool
type AttrGetType ActionVisibleVerticalPropertyInfo = Bool
type AttrLabel ActionVisibleVerticalPropertyInfo = "visible-vertical"
type AttrOrigin ActionVisibleVerticalPropertyInfo = Action
attrGet = getActionVisibleVertical
attrSet = setActionVisibleVertical
attrTransfer _ v = do
return v
attrConstruct = constructActionVisibleVertical
attrClear = undefined
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Action
type instance O.AttributeList Action = ActionAttributeList
type ActionAttributeList = ('[ '("actionGroup", ActionActionGroupPropertyInfo), '("alwaysShowImage", ActionAlwaysShowImagePropertyInfo), '("gicon", ActionGiconPropertyInfo), '("hideIfEmpty", ActionHideIfEmptyPropertyInfo), '("iconName", ActionIconNamePropertyInfo), '("isImportant", ActionIsImportantPropertyInfo), '("label", ActionLabelPropertyInfo), '("name", ActionNamePropertyInfo), '("sensitive", ActionSensitivePropertyInfo), '("shortLabel", ActionShortLabelPropertyInfo), '("stockId", ActionStockIdPropertyInfo), '("tooltip", ActionTooltipPropertyInfo), '("visible", ActionVisiblePropertyInfo), '("visibleHorizontal", ActionVisibleHorizontalPropertyInfo), '("visibleOverflown", ActionVisibleOverflownPropertyInfo), '("visibleVertical", ActionVisibleVerticalPropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
actionActionGroup :: AttrLabelProxy "actionGroup"
actionActionGroup = AttrLabelProxy
actionAlwaysShowImage :: AttrLabelProxy "alwaysShowImage"
actionAlwaysShowImage = AttrLabelProxy
actionGicon :: AttrLabelProxy "gicon"
actionGicon = AttrLabelProxy
actionHideIfEmpty :: AttrLabelProxy "hideIfEmpty"
actionHideIfEmpty = AttrLabelProxy
actionIconName :: AttrLabelProxy "iconName"
actionIconName = AttrLabelProxy
actionIsImportant :: AttrLabelProxy "isImportant"
actionIsImportant = AttrLabelProxy
actionLabel :: AttrLabelProxy "label"
actionLabel = AttrLabelProxy
actionName :: AttrLabelProxy "name"
actionName = AttrLabelProxy
actionSensitive :: AttrLabelProxy "sensitive"
actionSensitive = AttrLabelProxy
actionShortLabel :: AttrLabelProxy "shortLabel"
actionShortLabel = AttrLabelProxy
actionStockId :: AttrLabelProxy "stockId"
actionStockId = AttrLabelProxy
actionTooltip :: AttrLabelProxy "tooltip"
actionTooltip = AttrLabelProxy
actionVisible :: AttrLabelProxy "visible"
actionVisible = AttrLabelProxy
actionVisibleHorizontal :: AttrLabelProxy "visibleHorizontal"
actionVisibleHorizontal = AttrLabelProxy
actionVisibleOverflown :: AttrLabelProxy "visibleOverflown"
actionVisibleOverflown = AttrLabelProxy
actionVisibleVertical :: AttrLabelProxy "visibleVertical"
actionVisibleVertical = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Action = ActionSignalList
type ActionSignalList = ('[ '("activate", ActionActivateSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "gtk_action_new" gtk_action_new ::
CString ->
CString ->
CString ->
CString ->
IO (Ptr Action)
{-# DEPRECATED actionNew ["(Since version 3.10)","Use t'GI.Gio.Interfaces.Action.Action' instead, associating it to a widget with","t'GI.Gtk.Interfaces.Actionable.Actionable' or creating a t'GI.Gtk.Objects.Menu.Menu' with 'GI.Gtk.Objects.Menu.menuNewFromModel'"] #-}
actionNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
T.Text
-> Maybe (T.Text)
-> Maybe (T.Text)
-> Maybe (T.Text)
-> m Action
actionNew :: Text -> Maybe Text -> Maybe Text -> Maybe Text -> m Action
actionNew Text
name Maybe Text
label Maybe Text
tooltip Maybe Text
stockId = IO Action -> m Action
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Action -> m Action) -> IO Action -> m Action
forall a b. (a -> b) -> a -> b
$ do
CString
name' <- Text -> IO CString
textToCString Text
name
CString
maybeLabel <- case Maybe Text
label of
Maybe Text
Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
Just Text
jLabel -> do
CString
jLabel' <- Text -> IO CString
textToCString Text
jLabel
CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jLabel'
CString
maybeTooltip <- case Maybe Text
tooltip of
Maybe Text
Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
Just Text
jTooltip -> do
CString
jTooltip' <- Text -> IO CString
textToCString Text
jTooltip
CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jTooltip'
CString
maybeStockId <- case Maybe Text
stockId of
Maybe Text
Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
Just Text
jStockId -> do
CString
jStockId' <- Text -> IO CString
textToCString Text
jStockId
CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jStockId'
Ptr Action
result <- CString -> CString -> CString -> CString -> IO (Ptr Action)
gtk_action_new CString
name' CString
maybeLabel CString
maybeTooltip CString
maybeStockId
Text -> Ptr Action -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"actionNew" Ptr Action
result
Action
result' <- ((ManagedPtr Action -> Action) -> Ptr Action -> IO Action
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Action -> Action
Action) Ptr Action
result
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeLabel
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeTooltip
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeStockId
Action -> IO Action
forall (m :: * -> *) a. Monad m => a -> m a
return Action
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_action_activate" gtk_action_activate ::
Ptr Action ->
IO ()
{-# DEPRECATED actionActivate ["(Since version 3.10)","Use 'GI.Gio.Interfaces.ActionGroup.actionGroupActivateAction' on a t'GI.Gio.Interfaces.Action.Action' instead"] #-}
actionActivate ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> m ()
actionActivate :: a -> m ()
actionActivate a
action = 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 Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
Ptr Action -> IO ()
gtk_action_activate Ptr Action
action'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ActionActivateMethodInfo
instance (signature ~ (m ()), MonadIO m, IsAction a) => O.MethodInfo ActionActivateMethodInfo a signature where
overloadedMethod = actionActivate
#endif
foreign import ccall "gtk_action_block_activate" gtk_action_block_activate ::
Ptr Action ->
IO ()
{-# DEPRECATED actionBlockActivate ["(Since version 3.10)","Use 'GI.Gio.Objects.SimpleAction.simpleActionSetEnabled' to disable the","t'GI.Gio.Objects.SimpleAction.SimpleAction' instead"] #-}
actionBlockActivate ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> m ()
actionBlockActivate :: a -> m ()
actionBlockActivate a
action = 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 Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
Ptr Action -> IO ()
gtk_action_block_activate Ptr Action
action'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ActionBlockActivateMethodInfo
instance (signature ~ (m ()), MonadIO m, IsAction a) => O.MethodInfo ActionBlockActivateMethodInfo a signature where
overloadedMethod = actionBlockActivate
#endif
foreign import ccall "gtk_action_connect_accelerator" gtk_action_connect_accelerator ::
Ptr Action ->
IO ()
{-# DEPRECATED actionConnectAccelerator ["(Since version 3.10)","Use t'GI.Gio.Interfaces.Action.Action' and the accelerator group on an associated","t'GI.Gtk.Objects.Menu.Menu' instead"] #-}
actionConnectAccelerator ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> m ()
actionConnectAccelerator :: a -> m ()
actionConnectAccelerator a
action = 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 Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
Ptr Action -> IO ()
gtk_action_connect_accelerator Ptr Action
action'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ActionConnectAcceleratorMethodInfo
instance (signature ~ (m ()), MonadIO m, IsAction a) => O.MethodInfo ActionConnectAcceleratorMethodInfo a signature where
overloadedMethod = actionConnectAccelerator
#endif
foreign import ccall "gtk_action_create_icon" gtk_action_create_icon ::
Ptr Action ->
Int32 ->
IO (Ptr Gtk.Widget.Widget)
{-# DEPRECATED actionCreateIcon ["(Since version 3.10)","Use 'GI.Gio.Objects.MenuItem.menuItemSetIcon' to set an icon on a t'GI.Gio.Objects.MenuItem.MenuItem',","or 'GI.Gtk.Objects.Container.containerAdd' to add a t'GI.Gtk.Objects.Image.Image' to a t'GI.Gtk.Objects.Button.Button'"] #-}
actionCreateIcon ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> Int32
-> m Gtk.Widget.Widget
actionCreateIcon :: a -> Int32 -> m Widget
actionCreateIcon a
action Int32
iconSize = IO Widget -> m Widget
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Widget -> m Widget) -> IO Widget -> m Widget
forall a b. (a -> b) -> a -> b
$ do
Ptr Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
Ptr Widget
result <- Ptr Action -> Int32 -> IO (Ptr Widget)
gtk_action_create_icon Ptr Action
action' Int32
iconSize
Text -> Ptr Widget -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"actionCreateIcon" Ptr Widget
result
Widget
result' <- ((ManagedPtr Widget -> Widget) -> Ptr Widget -> IO Widget
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Widget -> Widget
Gtk.Widget.Widget) Ptr Widget
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
Widget -> IO Widget
forall (m :: * -> *) a. Monad m => a -> m a
return Widget
result'
#if defined(ENABLE_OVERLOADING)
data ActionCreateIconMethodInfo
instance (signature ~ (Int32 -> m Gtk.Widget.Widget), MonadIO m, IsAction a) => O.MethodInfo ActionCreateIconMethodInfo a signature where
overloadedMethod = actionCreateIcon
#endif
foreign import ccall "gtk_action_create_menu" ::
Ptr Action ->
IO (Ptr Gtk.Widget.Widget)
{-# DEPRECATED actionCreateMenu ["(Since version 3.10)","Use t'GI.Gio.Interfaces.Action.Action' and t'GI.Gio.Objects.MenuModel.MenuModel' instead, and create a","t'GI.Gtk.Objects.Menu.Menu' with 'GI.Gtk.Objects.Menu.menuNewFromModel'"] #-}
actionCreateMenu ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> m Gtk.Widget.Widget
a
action = IO Widget -> m Widget
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Widget -> m Widget) -> IO Widget -> m Widget
forall a b. (a -> b) -> a -> b
$ do
Ptr Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
Ptr Widget
result <- Ptr Action -> IO (Ptr Widget)
gtk_action_create_menu Ptr Action
action'
Text -> Ptr Widget -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"actionCreateMenu" Ptr Widget
result
Widget
result' <- ((ManagedPtr Widget -> Widget) -> Ptr Widget -> IO Widget
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Widget -> Widget
Gtk.Widget.Widget) Ptr Widget
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
Widget -> IO Widget
forall (m :: * -> *) a. Monad m => a -> m a
return Widget
result'
#if defined(ENABLE_OVERLOADING)
data ActionCreateMenuMethodInfo
instance (signature ~ (m Gtk.Widget.Widget), MonadIO m, IsAction a) => O.MethodInfo ActionCreateMenuMethodInfo a signature where
overloadedMethod = actionCreateMenu
#endif
foreign import ccall "gtk_action_create_menu_item" ::
Ptr Action ->
IO (Ptr Gtk.Widget.Widget)
{-# DEPRECATED actionCreateMenuItem ["(Since version 3.10)","Use 'GI.Gio.Objects.MenuItem.menuItemNew' and associate it with a t'GI.Gio.Interfaces.Action.Action'","instead."] #-}
actionCreateMenuItem ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> m Gtk.Widget.Widget
a
action = IO Widget -> m Widget
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Widget -> m Widget) -> IO Widget -> m Widget
forall a b. (a -> b) -> a -> b
$ do
Ptr Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
Ptr Widget
result <- Ptr Action -> IO (Ptr Widget)
gtk_action_create_menu_item Ptr Action
action'
Text -> Ptr Widget -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"actionCreateMenuItem" Ptr Widget
result
Widget
result' <- ((ManagedPtr Widget -> Widget) -> Ptr Widget -> IO Widget
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Widget -> Widget
Gtk.Widget.Widget) Ptr Widget
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
Widget -> IO Widget
forall (m :: * -> *) a. Monad m => a -> m a
return Widget
result'
#if defined(ENABLE_OVERLOADING)
data ActionCreateMenuItemMethodInfo
instance (signature ~ (m Gtk.Widget.Widget), MonadIO m, IsAction a) => O.MethodInfo ActionCreateMenuItemMethodInfo a signature where
overloadedMethod = actionCreateMenuItem
#endif
foreign import ccall "gtk_action_create_tool_item" gtk_action_create_tool_item ::
Ptr Action ->
IO (Ptr Gtk.Widget.Widget)
{-# DEPRECATED actionCreateToolItem ["(Since version 3.10)","Use a t'GI.Gtk.Objects.ToolItem.ToolItem' and associate it with a t'GI.Gio.Interfaces.Action.Action' using","'GI.Gtk.Interfaces.Actionable.actionableSetActionName' instead"] #-}
actionCreateToolItem ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> m Gtk.Widget.Widget
actionCreateToolItem :: a -> m Widget
actionCreateToolItem a
action = IO Widget -> m Widget
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Widget -> m Widget) -> IO Widget -> m Widget
forall a b. (a -> b) -> a -> b
$ do
Ptr Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
Ptr Widget
result <- Ptr Action -> IO (Ptr Widget)
gtk_action_create_tool_item Ptr Action
action'
Text -> Ptr Widget -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"actionCreateToolItem" Ptr Widget
result
Widget
result' <- ((ManagedPtr Widget -> Widget) -> Ptr Widget -> IO Widget
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Widget -> Widget
Gtk.Widget.Widget) Ptr Widget
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
Widget -> IO Widget
forall (m :: * -> *) a. Monad m => a -> m a
return Widget
result'
#if defined(ENABLE_OVERLOADING)
data ActionCreateToolItemMethodInfo
instance (signature ~ (m Gtk.Widget.Widget), MonadIO m, IsAction a) => O.MethodInfo ActionCreateToolItemMethodInfo a signature where
overloadedMethod = actionCreateToolItem
#endif
foreign import ccall "gtk_action_disconnect_accelerator" gtk_action_disconnect_accelerator ::
Ptr Action ->
IO ()
{-# DEPRECATED actionDisconnectAccelerator ["(Since version 3.10)","Use t'GI.Gio.Interfaces.Action.Action' and the accelerator group on an associated","t'GI.Gtk.Objects.Menu.Menu' instead"] #-}
actionDisconnectAccelerator ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> m ()
actionDisconnectAccelerator :: a -> m ()
actionDisconnectAccelerator a
action = 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 Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
Ptr Action -> IO ()
gtk_action_disconnect_accelerator Ptr Action
action'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ActionDisconnectAcceleratorMethodInfo
instance (signature ~ (m ()), MonadIO m, IsAction a) => O.MethodInfo ActionDisconnectAcceleratorMethodInfo a signature where
overloadedMethod = actionDisconnectAccelerator
#endif
foreign import ccall "gtk_action_get_accel_closure" gtk_action_get_accel_closure ::
Ptr Action ->
IO (Ptr (GClosure ()))
{-# DEPRECATED actionGetAccelClosure ["(Since version 3.10)","Use t'GI.Gio.Interfaces.Action.Action' and t'GI.Gtk.Objects.Menu.Menu' instead, which have no","equivalent for getting the accel closure"] #-}
actionGetAccelClosure ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> m (GClosure b)
actionGetAccelClosure :: a -> m (GClosure b)
actionGetAccelClosure a
action = IO (GClosure b) -> m (GClosure b)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure b) -> m (GClosure b))
-> IO (GClosure b) -> m (GClosure b)
forall a b. (a -> b) -> a -> b
$ do
Ptr Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
Ptr (GClosure ())
result <- Ptr Action -> IO (Ptr (GClosure ()))
gtk_action_get_accel_closure Ptr Action
action'
Text -> Ptr (GClosure ()) -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"actionGetAccelClosure" Ptr (GClosure ())
result
GClosure b
result' <- (Ptr (GClosure b) -> IO (GClosure b)
forall a. Ptr (GClosure a) -> IO (GClosure a)
B.GClosure.newGClosureFromPtr (Ptr (GClosure b) -> IO (GClosure b))
-> (Ptr (GClosure ()) -> Ptr (GClosure b))
-> Ptr (GClosure ())
-> IO (GClosure b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr (GClosure ()) -> Ptr (GClosure b)
forall a b. Ptr a -> Ptr b
FP.castPtr) Ptr (GClosure ())
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
GClosure b -> IO (GClosure b)
forall (m :: * -> *) a. Monad m => a -> m a
return GClosure b
result'
#if defined(ENABLE_OVERLOADING)
data ActionGetAccelClosureMethodInfo
instance (signature ~ (m (GClosure b)), MonadIO m, IsAction a) => O.MethodInfo ActionGetAccelClosureMethodInfo a signature where
overloadedMethod = actionGetAccelClosure
#endif
foreign import ccall "gtk_action_get_accel_path" gtk_action_get_accel_path ::
Ptr Action ->
IO CString
{-# DEPRECATED actionGetAccelPath ["(Since version 3.10)","Use t'GI.Gio.Interfaces.Action.Action' and the accelerator path on an associated","t'GI.Gtk.Objects.Menu.Menu' instead"] #-}
actionGetAccelPath ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> m T.Text
actionGetAccelPath :: a -> m Text
actionGetAccelPath a
action = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
Ptr Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
CString
result <- Ptr Action -> IO CString
gtk_action_get_accel_path Ptr Action
action'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"actionGetAccelPath" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data ActionGetAccelPathMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsAction a) => O.MethodInfo ActionGetAccelPathMethodInfo a signature where
overloadedMethod = actionGetAccelPath
#endif
foreign import ccall "gtk_action_get_always_show_image" gtk_action_get_always_show_image ::
Ptr Action ->
IO CInt
{-# DEPRECATED actionGetAlwaysShowImage ["(Since version 3.10)","Use 'GI.Gio.Objects.MenuItem.menuItemGetAttributeValue' on a t'GI.Gio.Objects.MenuItem.MenuItem'","instead"] #-}
actionGetAlwaysShowImage ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> m Bool
actionGetAlwaysShowImage :: a -> m Bool
actionGetAlwaysShowImage a
action = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
CInt
result <- Ptr Action -> IO CInt
gtk_action_get_always_show_image Ptr Action
action'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data ActionGetAlwaysShowImageMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsAction a) => O.MethodInfo ActionGetAlwaysShowImageMethodInfo a signature where
overloadedMethod = actionGetAlwaysShowImage
#endif
foreign import ccall "gtk_action_get_gicon" gtk_action_get_gicon ::
Ptr Action ->
IO (Ptr Gio.Icon.Icon)
{-# DEPRECATED actionGetGicon ["(Since version 3.10)","Use t'GI.Gio.Interfaces.Action.Action' instead, and","'GI.Gio.Objects.MenuItem.menuItemGetAttributeValue' to get an icon from a t'GI.Gio.Objects.MenuItem.MenuItem'","associated with a t'GI.Gio.Interfaces.Action.Action'"] #-}
actionGetGicon ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> m Gio.Icon.Icon
actionGetGicon :: a -> m Icon
actionGetGicon a
action = IO Icon -> m Icon
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Icon -> m Icon) -> IO Icon -> m Icon
forall a b. (a -> b) -> a -> b
$ do
Ptr Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
Ptr Icon
result <- Ptr Action -> IO (Ptr Icon)
gtk_action_get_gicon Ptr Action
action'
Text -> Ptr Icon -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"actionGetGicon" Ptr Icon
result
Icon
result' <- ((ManagedPtr Icon -> Icon) -> Ptr Icon -> IO Icon
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Icon -> Icon
Gio.Icon.Icon) Ptr Icon
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
Icon -> IO Icon
forall (m :: * -> *) a. Monad m => a -> m a
return Icon
result'
#if defined(ENABLE_OVERLOADING)
data ActionGetGiconMethodInfo
instance (signature ~ (m Gio.Icon.Icon), MonadIO m, IsAction a) => O.MethodInfo ActionGetGiconMethodInfo a signature where
overloadedMethod = actionGetGicon
#endif
foreign import ccall "gtk_action_get_icon_name" gtk_action_get_icon_name ::
Ptr Action ->
IO CString
{-# DEPRECATED actionGetIconName ["(Since version 3.10)","Use t'GI.Gio.Interfaces.Action.Action' instead, and","'GI.Gio.Objects.MenuItem.menuItemGetAttributeValue' to get an icon from a t'GI.Gio.Objects.MenuItem.MenuItem'","associated with a t'GI.Gio.Interfaces.Action.Action'"] #-}
actionGetIconName ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> m T.Text
actionGetIconName :: a -> m Text
actionGetIconName a
action = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
Ptr Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
CString
result <- Ptr Action -> IO CString
gtk_action_get_icon_name Ptr Action
action'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"actionGetIconName" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data ActionGetIconNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsAction a) => O.MethodInfo ActionGetIconNameMethodInfo a signature where
overloadedMethod = actionGetIconName
#endif
foreign import ccall "gtk_action_get_is_important" gtk_action_get_is_important ::
Ptr Action ->
IO CInt
{-# DEPRECATED actionGetIsImportant ["(Since version 3.10)","Use t'GI.Gio.Interfaces.Action.Action' instead, and control and monitor whether","labels are shown directly"] #-}
actionGetIsImportant ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> m Bool
actionGetIsImportant :: a -> m Bool
actionGetIsImportant a
action = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
CInt
result <- Ptr Action -> IO CInt
gtk_action_get_is_important Ptr Action
action'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data ActionGetIsImportantMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsAction a) => O.MethodInfo ActionGetIsImportantMethodInfo a signature where
overloadedMethod = actionGetIsImportant
#endif
foreign import ccall "gtk_action_get_label" gtk_action_get_label ::
Ptr Action ->
IO CString
{-# DEPRECATED actionGetLabel ["(Since version 3.10)","Use t'GI.Gio.Interfaces.Action.Action' instead, and get a label from a menu item","with 'GI.Gio.Objects.MenuItem.menuItemGetAttributeValue'. For t'GI.Gtk.Interfaces.Actionable.Actionable' widgets, use the","widget-specific API to get a label"] #-}
actionGetLabel ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> m T.Text
actionGetLabel :: a -> m Text
actionGetLabel a
action = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
Ptr Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
CString
result <- Ptr Action -> IO CString
gtk_action_get_label Ptr Action
action'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"actionGetLabel" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data ActionGetLabelMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsAction a) => O.MethodInfo ActionGetLabelMethodInfo a signature where
overloadedMethod = actionGetLabel
#endif
foreign import ccall "gtk_action_get_name" gtk_action_get_name ::
Ptr Action ->
IO CString
{-# DEPRECATED actionGetName ["(Since version 3.10)","Use 'GI.Gio.Interfaces.Action.actionGetName' on a t'GI.Gio.Interfaces.Action.Action' instead"] #-}
actionGetName ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> m T.Text
actionGetName :: a -> m Text
actionGetName a
action = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
Ptr Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
CString
result <- Ptr Action -> IO CString
gtk_action_get_name Ptr Action
action'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"actionGetName" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data ActionGetNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsAction a) => O.MethodInfo ActionGetNameMethodInfo a signature where
overloadedMethod = actionGetName
#endif
foreign import ccall "gtk_action_get_proxies" gtk_action_get_proxies ::
Ptr Action ->
IO (Ptr (GSList (Ptr Gtk.Widget.Widget)))
{-# DEPRECATED actionGetProxies ["(Since version 3.10)"] #-}
actionGetProxies ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> m [Gtk.Widget.Widget]
actionGetProxies :: a -> m [Widget]
actionGetProxies a
action = IO [Widget] -> m [Widget]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Widget] -> m [Widget]) -> IO [Widget] -> m [Widget]
forall a b. (a -> b) -> a -> b
$ do
Ptr Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
Ptr (GSList (Ptr Widget))
result <- Ptr Action -> IO (Ptr (GSList (Ptr Widget)))
gtk_action_get_proxies Ptr Action
action'
[Ptr Widget]
result' <- Ptr (GSList (Ptr Widget)) -> IO [Ptr Widget]
forall a. Ptr (GSList (Ptr a)) -> IO [Ptr a]
unpackGSList Ptr (GSList (Ptr Widget))
result
[Widget]
result'' <- (Ptr Widget -> IO Widget) -> [Ptr Widget] -> IO [Widget]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr Widget -> Widget) -> Ptr Widget -> IO Widget
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Widget -> Widget
Gtk.Widget.Widget) [Ptr Widget]
result'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
[Widget] -> IO [Widget]
forall (m :: * -> *) a. Monad m => a -> m a
return [Widget]
result''
#if defined(ENABLE_OVERLOADING)
data ActionGetProxiesMethodInfo
instance (signature ~ (m [Gtk.Widget.Widget]), MonadIO m, IsAction a) => O.MethodInfo ActionGetProxiesMethodInfo a signature where
overloadedMethod = actionGetProxies
#endif
foreign import ccall "gtk_action_get_sensitive" gtk_action_get_sensitive ::
Ptr Action ->
IO CInt
{-# DEPRECATED actionGetSensitive ["(Since version 3.10)","Use 'GI.Gio.Interfaces.Action.actionGetEnabled' on a t'GI.Gio.Interfaces.Action.Action'","instead"] #-}
actionGetSensitive ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> m Bool
actionGetSensitive :: a -> m Bool
actionGetSensitive a
action = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
CInt
result <- Ptr Action -> IO CInt
gtk_action_get_sensitive Ptr Action
action'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data ActionGetSensitiveMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsAction a) => O.MethodInfo ActionGetSensitiveMethodInfo a signature where
overloadedMethod = actionGetSensitive
#endif
foreign import ccall "gtk_action_get_short_label" gtk_action_get_short_label ::
Ptr Action ->
IO CString
{-# DEPRECATED actionGetShortLabel ["(Since version 3.10)","Use t'GI.Gio.Interfaces.Action.Action' instead, which has no equivalent of short","labels"] #-}
actionGetShortLabel ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> m T.Text
actionGetShortLabel :: a -> m Text
actionGetShortLabel a
action = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
Ptr Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
CString
result <- Ptr Action -> IO CString
gtk_action_get_short_label Ptr Action
action'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"actionGetShortLabel" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data ActionGetShortLabelMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsAction a) => O.MethodInfo ActionGetShortLabelMethodInfo a signature where
overloadedMethod = actionGetShortLabel
#endif
foreign import ccall "gtk_action_get_stock_id" gtk_action_get_stock_id ::
Ptr Action ->
IO CString
{-# DEPRECATED actionGetStockId ["(Since version 3.10)","Use t'GI.Gio.Interfaces.Action.Action' instead, which has no equivalent of stock","items"] #-}
actionGetStockId ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> m T.Text
actionGetStockId :: a -> m Text
actionGetStockId a
action = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
Ptr Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
CString
result <- Ptr Action -> IO CString
gtk_action_get_stock_id Ptr Action
action'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"actionGetStockId" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data ActionGetStockIdMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsAction a) => O.MethodInfo ActionGetStockIdMethodInfo a signature where
overloadedMethod = actionGetStockId
#endif
foreign import ccall "gtk_action_get_tooltip" gtk_action_get_tooltip ::
Ptr Action ->
IO CString
{-# DEPRECATED actionGetTooltip ["(Since version 3.10)","Use t'GI.Gio.Interfaces.Action.Action' instead, and get tooltips from associated","t'GI.Gtk.Interfaces.Actionable.Actionable' widgets with 'GI.Gtk.Objects.Widget.widgetGetTooltipText'"] #-}
actionGetTooltip ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> m T.Text
actionGetTooltip :: a -> m Text
actionGetTooltip a
action = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
Ptr Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
CString
result <- Ptr Action -> IO CString
gtk_action_get_tooltip Ptr Action
action'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"actionGetTooltip" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data ActionGetTooltipMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsAction a) => O.MethodInfo ActionGetTooltipMethodInfo a signature where
overloadedMethod = actionGetTooltip
#endif
foreign import ccall "gtk_action_get_visible" gtk_action_get_visible ::
Ptr Action ->
IO CInt
{-# DEPRECATED actionGetVisible ["(Since version 3.10)","Use t'GI.Gio.Interfaces.Action.Action' instead, and control and monitor the state of","t'GI.Gtk.Interfaces.Actionable.Actionable' widgets directly"] #-}
actionGetVisible ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> m Bool
actionGetVisible :: a -> m Bool
actionGetVisible a
action = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
CInt
result <- Ptr Action -> IO CInt
gtk_action_get_visible Ptr Action
action'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data ActionGetVisibleMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsAction a) => O.MethodInfo ActionGetVisibleMethodInfo a signature where
overloadedMethod = actionGetVisible
#endif
foreign import ccall "gtk_action_get_visible_horizontal" gtk_action_get_visible_horizontal ::
Ptr Action ->
IO CInt
{-# DEPRECATED actionGetVisibleHorizontal ["(Since version 3.10)","Use t'GI.Gio.Interfaces.Action.Action' instead, and control and monitor the","visibility of associated widgets and menu items directly"] #-}
actionGetVisibleHorizontal ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> m Bool
actionGetVisibleHorizontal :: a -> m Bool
actionGetVisibleHorizontal a
action = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
CInt
result <- Ptr Action -> IO CInt
gtk_action_get_visible_horizontal Ptr Action
action'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data ActionGetVisibleHorizontalMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsAction a) => O.MethodInfo ActionGetVisibleHorizontalMethodInfo a signature where
overloadedMethod = actionGetVisibleHorizontal
#endif
foreign import ccall "gtk_action_get_visible_vertical" gtk_action_get_visible_vertical ::
Ptr Action ->
IO CInt
{-# DEPRECATED actionGetVisibleVertical ["(Since version 3.10)","Use t'GI.Gio.Interfaces.Action.Action' instead, and control and monitor the","visibility of associated widgets and menu items directly"] #-}
actionGetVisibleVertical ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> m Bool
actionGetVisibleVertical :: a -> m Bool
actionGetVisibleVertical a
action = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
CInt
result <- Ptr Action -> IO CInt
gtk_action_get_visible_vertical Ptr Action
action'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data ActionGetVisibleVerticalMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsAction a) => O.MethodInfo ActionGetVisibleVerticalMethodInfo a signature where
overloadedMethod = actionGetVisibleVertical
#endif
foreign import ccall "gtk_action_is_sensitive" gtk_action_is_sensitive ::
Ptr Action ->
IO CInt
{-# DEPRECATED actionIsSensitive ["(Since version 3.10)","Use 'GI.Gio.Interfaces.Action.actionGetEnabled' on a t'GI.Gio.Interfaces.Action.Action'","instead"] #-}
actionIsSensitive ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> m Bool
actionIsSensitive :: a -> m Bool
actionIsSensitive a
action = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
CInt
result <- Ptr Action -> IO CInt
gtk_action_is_sensitive Ptr Action
action'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data ActionIsSensitiveMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsAction a) => O.MethodInfo ActionIsSensitiveMethodInfo a signature where
overloadedMethod = actionIsSensitive
#endif
foreign import ccall "gtk_action_is_visible" gtk_action_is_visible ::
Ptr Action ->
IO CInt
{-# DEPRECATED actionIsVisible ["(Since version 3.10)","Use t'GI.Gio.Interfaces.Action.Action' instead, and control and monitor the state of","t'GI.Gtk.Interfaces.Actionable.Actionable' widgets directly"] #-}
actionIsVisible ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> m Bool
actionIsVisible :: a -> m Bool
actionIsVisible a
action = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
CInt
result <- Ptr Action -> IO CInt
gtk_action_is_visible Ptr Action
action'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data ActionIsVisibleMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsAction a) => O.MethodInfo ActionIsVisibleMethodInfo a signature where
overloadedMethod = actionIsVisible
#endif
foreign import ccall "gtk_action_set_accel_group" gtk_action_set_accel_group ::
Ptr Action ->
Ptr Gtk.AccelGroup.AccelGroup ->
IO ()
{-# DEPRECATED actionSetAccelGroup ["(Since version 3.10)","Use t'GI.Gio.Interfaces.Action.Action' and the accelerator group on an associated","t'GI.Gtk.Objects.Menu.Menu' instead"] #-}
actionSetAccelGroup ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a, Gtk.AccelGroup.IsAccelGroup b) =>
a
-> Maybe (b)
-> m ()
actionSetAccelGroup :: a -> Maybe b -> m ()
actionSetAccelGroup a
action Maybe b
accelGroup = 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 Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
Ptr AccelGroup
maybeAccelGroup <- case Maybe b
accelGroup of
Maybe b
Nothing -> Ptr AccelGroup -> IO (Ptr AccelGroup)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr AccelGroup
forall a. Ptr a
nullPtr
Just b
jAccelGroup -> do
Ptr AccelGroup
jAccelGroup' <- b -> IO (Ptr AccelGroup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jAccelGroup
Ptr AccelGroup -> IO (Ptr AccelGroup)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr AccelGroup
jAccelGroup'
Ptr Action -> Ptr AccelGroup -> IO ()
gtk_action_set_accel_group Ptr Action
action' Ptr AccelGroup
maybeAccelGroup
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
accelGroup b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ActionSetAccelGroupMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsAction a, Gtk.AccelGroup.IsAccelGroup b) => O.MethodInfo ActionSetAccelGroupMethodInfo a signature where
overloadedMethod = actionSetAccelGroup
#endif
foreign import ccall "gtk_action_set_accel_path" gtk_action_set_accel_path ::
Ptr Action ->
CString ->
IO ()
{-# DEPRECATED actionSetAccelPath ["(Since version 3.10)","Use t'GI.Gio.Interfaces.Action.Action' and the accelerator path on an associated","t'GI.Gtk.Objects.Menu.Menu' instead"] #-}
actionSetAccelPath ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> T.Text
-> m ()
actionSetAccelPath :: a -> Text -> m ()
actionSetAccelPath a
action Text
accelPath = 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 Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
CString
accelPath' <- Text -> IO CString
textToCString Text
accelPath
Ptr Action -> CString -> IO ()
gtk_action_set_accel_path Ptr Action
action' CString
accelPath'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
accelPath'
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ActionSetAccelPathMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsAction a) => O.MethodInfo ActionSetAccelPathMethodInfo a signature where
overloadedMethod = actionSetAccelPath
#endif
foreign import ccall "gtk_action_set_always_show_image" gtk_action_set_always_show_image ::
Ptr Action ->
CInt ->
IO ()
{-# DEPRECATED actionSetAlwaysShowImage ["(Since version 3.10)","Use 'GI.Gio.Objects.MenuItem.menuItemSetIcon' on a t'GI.Gio.Objects.MenuItem.MenuItem' instead, if the","item should have an image"] #-}
actionSetAlwaysShowImage ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> Bool
-> m ()
actionSetAlwaysShowImage :: a -> Bool -> m ()
actionSetAlwaysShowImage a
action Bool
alwaysShow = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
let alwaysShow' :: CInt
alwaysShow' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
alwaysShow
Ptr Action -> CInt -> IO ()
gtk_action_set_always_show_image Ptr Action
action' CInt
alwaysShow'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ActionSetAlwaysShowImageMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsAction a) => O.MethodInfo ActionSetAlwaysShowImageMethodInfo a signature where
overloadedMethod = actionSetAlwaysShowImage
#endif
foreign import ccall "gtk_action_set_gicon" gtk_action_set_gicon ::
Ptr Action ->
Ptr Gio.Icon.Icon ->
IO ()
{-# DEPRECATED actionSetGicon ["(Since version 3.10)","Use t'GI.Gio.Interfaces.Action.Action' instead, and 'GI.Gio.Objects.MenuItem.menuItemSetIcon' to set an","icon on a t'GI.Gio.Objects.MenuItem.MenuItem' associated with a t'GI.Gio.Interfaces.Action.Action', or 'GI.Gtk.Objects.Container.containerAdd' to","add a t'GI.Gtk.Objects.Image.Image' to a t'GI.Gtk.Objects.Button.Button'"] #-}
actionSetGicon ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a, Gio.Icon.IsIcon b) =>
a
-> b
-> m ()
actionSetGicon :: a -> b -> m ()
actionSetGicon a
action b
icon = 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 Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
Ptr Icon
icon' <- b -> IO (Ptr Icon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
icon
Ptr Action -> Ptr Icon -> IO ()
gtk_action_set_gicon Ptr Action
action' Ptr Icon
icon'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
icon
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ActionSetGiconMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsAction a, Gio.Icon.IsIcon b) => O.MethodInfo ActionSetGiconMethodInfo a signature where
overloadedMethod = actionSetGicon
#endif
foreign import ccall "gtk_action_set_icon_name" gtk_action_set_icon_name ::
Ptr Action ->
CString ->
IO ()
{-# DEPRECATED actionSetIconName ["(Since version 3.10)","Use t'GI.Gio.Interfaces.Action.Action' instead, and 'GI.Gio.Objects.MenuItem.menuItemSetIcon' to set an","icon on a t'GI.Gio.Objects.MenuItem.MenuItem' associated with a t'GI.Gio.Interfaces.Action.Action', or 'GI.Gtk.Objects.Container.containerAdd' to","add a t'GI.Gtk.Objects.Image.Image' to a t'GI.Gtk.Objects.Button.Button'"] #-}
actionSetIconName ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> T.Text
-> m ()
actionSetIconName :: a -> Text -> m ()
actionSetIconName a
action Text
iconName = 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 Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
CString
iconName' <- Text -> IO CString
textToCString Text
iconName
Ptr Action -> CString -> IO ()
gtk_action_set_icon_name Ptr Action
action' CString
iconName'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
iconName'
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ActionSetIconNameMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsAction a) => O.MethodInfo ActionSetIconNameMethodInfo a signature where
overloadedMethod = actionSetIconName
#endif
foreign import ccall "gtk_action_set_is_important" gtk_action_set_is_important ::
Ptr Action ->
CInt ->
IO ()
{-# DEPRECATED actionSetIsImportant ["(Since version 3.10)","Use t'GI.Gio.Interfaces.Action.Action' instead, and control and monitor whether","labels are shown directly"] #-}
actionSetIsImportant ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> Bool
-> m ()
actionSetIsImportant :: a -> Bool -> m ()
actionSetIsImportant a
action Bool
isImportant = 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 Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
let isImportant' :: CInt
isImportant' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
isImportant
Ptr Action -> CInt -> IO ()
gtk_action_set_is_important Ptr Action
action' CInt
isImportant'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ActionSetIsImportantMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsAction a) => O.MethodInfo ActionSetIsImportantMethodInfo a signature where
overloadedMethod = actionSetIsImportant
#endif
foreign import ccall "gtk_action_set_label" gtk_action_set_label ::
Ptr Action ->
CString ->
IO ()
{-# DEPRECATED actionSetLabel ["(Since version 3.10)","Use t'GI.Gio.Interfaces.Action.Action' instead, and set a label on a menu item with","'GI.Gio.Objects.MenuItem.menuItemSetLabel'. For t'GI.Gtk.Interfaces.Actionable.Actionable' widgets, use the widget-specific","API to set a label"] #-}
actionSetLabel ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> T.Text
-> m ()
actionSetLabel :: a -> Text -> m ()
actionSetLabel a
action Text
label = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
CString
label' <- Text -> IO CString
textToCString Text
label
Ptr Action -> CString -> IO ()
gtk_action_set_label Ptr Action
action' CString
label'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
label'
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ActionSetLabelMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsAction a) => O.MethodInfo ActionSetLabelMethodInfo a signature where
overloadedMethod = actionSetLabel
#endif
foreign import ccall "gtk_action_set_sensitive" gtk_action_set_sensitive ::
Ptr Action ->
CInt ->
IO ()
{-# DEPRECATED actionSetSensitive ["(Since version 3.10)","Use 'GI.Gio.Objects.SimpleAction.simpleActionSetEnabled' on a t'GI.Gio.Objects.SimpleAction.SimpleAction'","instead"] #-}
actionSetSensitive ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> Bool
-> m ()
actionSetSensitive :: a -> Bool -> m ()
actionSetSensitive a
action Bool
sensitive = 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 Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
let sensitive' :: CInt
sensitive' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
sensitive
Ptr Action -> CInt -> IO ()
gtk_action_set_sensitive Ptr Action
action' CInt
sensitive'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ActionSetSensitiveMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsAction a) => O.MethodInfo ActionSetSensitiveMethodInfo a signature where
overloadedMethod = actionSetSensitive
#endif
foreign import ccall "gtk_action_set_short_label" gtk_action_set_short_label ::
Ptr Action ->
CString ->
IO ()
{-# DEPRECATED actionSetShortLabel ["(Since version 3.10)","Use t'GI.Gio.Interfaces.Action.Action' instead, which has no equivalent of short","labels"] #-}
actionSetShortLabel ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> T.Text
-> m ()
actionSetShortLabel :: a -> Text -> m ()
actionSetShortLabel a
action Text
shortLabel = 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 Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
CString
shortLabel' <- Text -> IO CString
textToCString Text
shortLabel
Ptr Action -> CString -> IO ()
gtk_action_set_short_label Ptr Action
action' CString
shortLabel'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
shortLabel'
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ActionSetShortLabelMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsAction a) => O.MethodInfo ActionSetShortLabelMethodInfo a signature where
overloadedMethod = actionSetShortLabel
#endif
foreign import ccall "gtk_action_set_stock_id" gtk_action_set_stock_id ::
Ptr Action ->
CString ->
IO ()
{-# DEPRECATED actionSetStockId ["(Since version 3.10)","Use t'GI.Gio.Interfaces.Action.Action' instead, which has no equivalent of stock","items"] #-}
actionSetStockId ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> T.Text
-> m ()
actionSetStockId :: a -> Text -> m ()
actionSetStockId a
action Text
stockId = 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 Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
CString
stockId' <- Text -> IO CString
textToCString Text
stockId
Ptr Action -> CString -> IO ()
gtk_action_set_stock_id Ptr Action
action' CString
stockId'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
stockId'
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ActionSetStockIdMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsAction a) => O.MethodInfo ActionSetStockIdMethodInfo a signature where
overloadedMethod = actionSetStockId
#endif
foreign import ccall "gtk_action_set_tooltip" gtk_action_set_tooltip ::
Ptr Action ->
CString ->
IO ()
{-# DEPRECATED actionSetTooltip ["(Since version 3.10)","Use t'GI.Gio.Interfaces.Action.Action' instead, and set tooltips on associated","t'GI.Gtk.Interfaces.Actionable.Actionable' widgets with 'GI.Gtk.Objects.Widget.widgetSetTooltipText'"] #-}
actionSetTooltip ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> T.Text
-> m ()
actionSetTooltip :: a -> Text -> m ()
actionSetTooltip a
action Text
tooltip = 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 Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
CString
tooltip' <- Text -> IO CString
textToCString Text
tooltip
Ptr Action -> CString -> IO ()
gtk_action_set_tooltip Ptr Action
action' CString
tooltip'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
tooltip'
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ActionSetTooltipMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsAction a) => O.MethodInfo ActionSetTooltipMethodInfo a signature where
overloadedMethod = actionSetTooltip
#endif
foreign import ccall "gtk_action_set_visible" gtk_action_set_visible ::
Ptr Action ->
CInt ->
IO ()
{-# DEPRECATED actionSetVisible ["(Since version 3.10)","Use t'GI.Gio.Interfaces.Action.Action' instead, and control and monitor the state of","t'GI.Gtk.Interfaces.Actionable.Actionable' widgets directly"] #-}
actionSetVisible ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> Bool
-> m ()
actionSetVisible :: a -> Bool -> m ()
actionSetVisible a
action Bool
visible = 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 Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
let visible' :: CInt
visible' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
visible
Ptr Action -> CInt -> IO ()
gtk_action_set_visible Ptr Action
action' CInt
visible'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ActionSetVisibleMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsAction a) => O.MethodInfo ActionSetVisibleMethodInfo a signature where
overloadedMethod = actionSetVisible
#endif
foreign import ccall "gtk_action_set_visible_horizontal" gtk_action_set_visible_horizontal ::
Ptr Action ->
CInt ->
IO ()
{-# DEPRECATED actionSetVisibleHorizontal ["(Since version 3.10)","Use t'GI.Gio.Interfaces.Action.Action' instead, and control and monitor the","visibility of associated widgets and menu items directly"] #-}
actionSetVisibleHorizontal ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> Bool
-> m ()
actionSetVisibleHorizontal :: a -> Bool -> m ()
actionSetVisibleHorizontal a
action Bool
visibleHorizontal = 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 Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
let visibleHorizontal' :: CInt
visibleHorizontal' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
visibleHorizontal
Ptr Action -> CInt -> IO ()
gtk_action_set_visible_horizontal Ptr Action
action' CInt
visibleHorizontal'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ActionSetVisibleHorizontalMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsAction a) => O.MethodInfo ActionSetVisibleHorizontalMethodInfo a signature where
overloadedMethod = actionSetVisibleHorizontal
#endif
foreign import ccall "gtk_action_set_visible_vertical" gtk_action_set_visible_vertical ::
Ptr Action ->
CInt ->
IO ()
{-# DEPRECATED actionSetVisibleVertical ["(Since version 3.10)","Use t'GI.Gio.Interfaces.Action.Action' instead, and control and monitor the","visibility of associated widgets and menu items directly"] #-}
actionSetVisibleVertical ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> Bool
-> m ()
actionSetVisibleVertical :: a -> Bool -> m ()
actionSetVisibleVertical a
action Bool
visibleVertical = 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 Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
let visibleVertical' :: CInt
visibleVertical' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
visibleVertical
Ptr Action -> CInt -> IO ()
gtk_action_set_visible_vertical Ptr Action
action' CInt
visibleVertical'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ActionSetVisibleVerticalMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsAction a) => O.MethodInfo ActionSetVisibleVerticalMethodInfo a signature where
overloadedMethod = actionSetVisibleVertical
#endif
foreign import ccall "gtk_action_unblock_activate" gtk_action_unblock_activate ::
Ptr Action ->
IO ()
{-# DEPRECATED actionUnblockActivate ["(Since version 3.10)","Use 'GI.Gio.Objects.SimpleAction.simpleActionSetEnabled' to enable the","t'GI.Gio.Objects.SimpleAction.SimpleAction' instead"] #-}
actionUnblockActivate ::
(B.CallStack.HasCallStack, MonadIO m, IsAction a) =>
a
-> m ()
actionUnblockActivate :: a -> m ()
actionUnblockActivate a
action = 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 Action
action' <- a -> IO (Ptr Action)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
action
Ptr Action -> IO ()
gtk_action_unblock_activate Ptr Action
action'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
action
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ActionUnblockActivateMethodInfo
instance (signature ~ (m ()), MonadIO m, IsAction a) => O.MethodInfo ActionUnblockActivateMethodInfo a signature where
overloadedMethod = actionUnblockActivate
#endif