{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- This is the t'GI.GObject.Objects.Object.Object' based object that represents a menu
-- item.  It gets created the same on both the client and
-- the server side and libdbusmenu-glib does the work of making
-- this object model appear on both sides of DBus.  Simple
-- really, though through updates and people coming on and off
-- the bus it can lead to lots of fun complex scenarios.

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

module GI.Dbusmenu.Objects.Menuitem
    ( 

-- * Exported types
    Menuitem(..)                            ,
    IsMenuitem                              ,
    toMenuitem                              ,
    noMenuitem                              ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveMenuitemMethod                   ,
#endif


-- ** childAddPosition #method:childAddPosition#

#if defined(ENABLE_OVERLOADING)
    MenuitemChildAddPositionMethodInfo      ,
#endif
    menuitemChildAddPosition                ,


-- ** childAppend #method:childAppend#

#if defined(ENABLE_OVERLOADING)
    MenuitemChildAppendMethodInfo           ,
#endif
    menuitemChildAppend                     ,


-- ** childDelete #method:childDelete#

#if defined(ENABLE_OVERLOADING)
    MenuitemChildDeleteMethodInfo           ,
#endif
    menuitemChildDelete                     ,


-- ** childFind #method:childFind#

#if defined(ENABLE_OVERLOADING)
    MenuitemChildFindMethodInfo             ,
#endif
    menuitemChildFind                       ,


-- ** childPrepend #method:childPrepend#

#if defined(ENABLE_OVERLOADING)
    MenuitemChildPrependMethodInfo          ,
#endif
    menuitemChildPrepend                    ,


-- ** childReorder #method:childReorder#

#if defined(ENABLE_OVERLOADING)
    MenuitemChildReorderMethodInfo          ,
#endif
    menuitemChildReorder                    ,


-- ** findId #method:findId#

#if defined(ENABLE_OVERLOADING)
    MenuitemFindIdMethodInfo                ,
#endif
    menuitemFindId                          ,


-- ** foreach #method:foreach#

#if defined(ENABLE_OVERLOADING)
    MenuitemForeachMethodInfo               ,
#endif
    menuitemForeach                         ,


-- ** getChildren #method:getChildren#

#if defined(ENABLE_OVERLOADING)
    MenuitemGetChildrenMethodInfo           ,
#endif
    menuitemGetChildren                     ,


-- ** getId #method:getId#

#if defined(ENABLE_OVERLOADING)
    MenuitemGetIdMethodInfo                 ,
#endif
    menuitemGetId                           ,


-- ** getParent #method:getParent#

#if defined(ENABLE_OVERLOADING)
    MenuitemGetParentMethodInfo             ,
#endif
    menuitemGetParent                       ,


-- ** getPosition #method:getPosition#

#if defined(ENABLE_OVERLOADING)
    MenuitemGetPositionMethodInfo           ,
#endif
    menuitemGetPosition                     ,


-- ** getPositionRealized #method:getPositionRealized#

#if defined(ENABLE_OVERLOADING)
    MenuitemGetPositionRealizedMethodInfo   ,
#endif
    menuitemGetPositionRealized             ,


-- ** getRoot #method:getRoot#

#if defined(ENABLE_OVERLOADING)
    MenuitemGetRootMethodInfo               ,
#endif
    menuitemGetRoot                         ,


-- ** handleEvent #method:handleEvent#

#if defined(ENABLE_OVERLOADING)
    MenuitemHandleEventMethodInfo           ,
#endif
    menuitemHandleEvent                     ,


-- ** new #method:new#

    menuitemNew                             ,


-- ** newWithId #method:newWithId#

    menuitemNewWithId                       ,


-- ** propertiesCopy #method:propertiesCopy#

#if defined(ENABLE_OVERLOADING)
    MenuitemPropertiesCopyMethodInfo        ,
#endif
    menuitemPropertiesCopy                  ,


-- ** propertiesList #method:propertiesList#

#if defined(ENABLE_OVERLOADING)
    MenuitemPropertiesListMethodInfo        ,
#endif
    menuitemPropertiesList                  ,


-- ** propertyExist #method:propertyExist#

#if defined(ENABLE_OVERLOADING)
    MenuitemPropertyExistMethodInfo         ,
#endif
    menuitemPropertyExist                   ,


-- ** propertyGet #method:propertyGet#

#if defined(ENABLE_OVERLOADING)
    MenuitemPropertyGetMethodInfo           ,
#endif
    menuitemPropertyGet                     ,


-- ** propertyGetBool #method:propertyGetBool#

#if defined(ENABLE_OVERLOADING)
    MenuitemPropertyGetBoolMethodInfo       ,
#endif
    menuitemPropertyGetBool                 ,


-- ** propertyGetByteArray #method:propertyGetByteArray#

#if defined(ENABLE_OVERLOADING)
    MenuitemPropertyGetByteArrayMethodInfo  ,
#endif
    menuitemPropertyGetByteArray            ,


-- ** propertyGetInt #method:propertyGetInt#

#if defined(ENABLE_OVERLOADING)
    MenuitemPropertyGetIntMethodInfo        ,
#endif
    menuitemPropertyGetInt                  ,


-- ** propertyGetVariant #method:propertyGetVariant#

#if defined(ENABLE_OVERLOADING)
    MenuitemPropertyGetVariantMethodInfo    ,
#endif
    menuitemPropertyGetVariant              ,


-- ** propertyRemove #method:propertyRemove#

#if defined(ENABLE_OVERLOADING)
    MenuitemPropertyRemoveMethodInfo        ,
#endif
    menuitemPropertyRemove                  ,


-- ** propertySet #method:propertySet#

#if defined(ENABLE_OVERLOADING)
    MenuitemPropertySetMethodInfo           ,
#endif
    menuitemPropertySet                     ,


-- ** propertySetBool #method:propertySetBool#

#if defined(ENABLE_OVERLOADING)
    MenuitemPropertySetBoolMethodInfo       ,
#endif
    menuitemPropertySetBool                 ,


-- ** propertySetByteArray #method:propertySetByteArray#

#if defined(ENABLE_OVERLOADING)
    MenuitemPropertySetByteArrayMethodInfo  ,
#endif
    menuitemPropertySetByteArray            ,


-- ** propertySetInt #method:propertySetInt#

#if defined(ENABLE_OVERLOADING)
    MenuitemPropertySetIntMethodInfo        ,
#endif
    menuitemPropertySetInt                  ,


-- ** propertySetVariant #method:propertySetVariant#

#if defined(ENABLE_OVERLOADING)
    MenuitemPropertySetVariantMethodInfo    ,
#endif
    menuitemPropertySetVariant              ,


-- ** sendAboutToShow #method:sendAboutToShow#

#if defined(ENABLE_OVERLOADING)
    MenuitemSendAboutToShowMethodInfo       ,
#endif
    menuitemSendAboutToShow                 ,


-- ** setParent #method:setParent#

#if defined(ENABLE_OVERLOADING)
    MenuitemSetParentMethodInfo             ,
#endif
    menuitemSetParent                       ,


-- ** setRoot #method:setRoot#

#if defined(ENABLE_OVERLOADING)
    MenuitemSetRootMethodInfo               ,
#endif
    menuitemSetRoot                         ,


-- ** showToUser #method:showToUser#

#if defined(ENABLE_OVERLOADING)
    MenuitemShowToUserMethodInfo            ,
#endif
    menuitemShowToUser                      ,


-- ** takeChildren #method:takeChildren#

#if defined(ENABLE_OVERLOADING)
    MenuitemTakeChildrenMethodInfo          ,
#endif
    menuitemTakeChildren                    ,


-- ** unparent #method:unparent#

#if defined(ENABLE_OVERLOADING)
    MenuitemUnparentMethodInfo              ,
#endif
    menuitemUnparent                        ,




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

#if defined(ENABLE_OVERLOADING)
    MenuitemIdPropertyInfo                  ,
#endif
    constructMenuitemId                     ,
    getMenuitemId                           ,
#if defined(ENABLE_OVERLOADING)
    menuitemId                              ,
#endif




 -- * Signals
-- ** aboutToShow #signal:aboutToShow#

    C_MenuitemAboutToShowCallback           ,
    MenuitemAboutToShowCallback             ,
#if defined(ENABLE_OVERLOADING)
    MenuitemAboutToShowSignalInfo           ,
#endif
    afterMenuitemAboutToShow                ,
    genClosure_MenuitemAboutToShow          ,
    mk_MenuitemAboutToShowCallback          ,
    noMenuitemAboutToShowCallback           ,
    onMenuitemAboutToShow                   ,
    wrap_MenuitemAboutToShowCallback        ,


-- ** childAdded #signal:childAdded#

    C_MenuitemChildAddedCallback            ,
    MenuitemChildAddedCallback              ,
#if defined(ENABLE_OVERLOADING)
    MenuitemChildAddedSignalInfo            ,
#endif
    afterMenuitemChildAdded                 ,
    genClosure_MenuitemChildAdded           ,
    mk_MenuitemChildAddedCallback           ,
    noMenuitemChildAddedCallback            ,
    onMenuitemChildAdded                    ,
    wrap_MenuitemChildAddedCallback         ,


-- ** childMoved #signal:childMoved#

    C_MenuitemChildMovedCallback            ,
    MenuitemChildMovedCallback              ,
#if defined(ENABLE_OVERLOADING)
    MenuitemChildMovedSignalInfo            ,
#endif
    afterMenuitemChildMoved                 ,
    genClosure_MenuitemChildMoved           ,
    mk_MenuitemChildMovedCallback           ,
    noMenuitemChildMovedCallback            ,
    onMenuitemChildMoved                    ,
    wrap_MenuitemChildMovedCallback         ,


-- ** childRemoved #signal:childRemoved#

    C_MenuitemChildRemovedCallback          ,
    MenuitemChildRemovedCallback            ,
#if defined(ENABLE_OVERLOADING)
    MenuitemChildRemovedSignalInfo          ,
#endif
    afterMenuitemChildRemoved               ,
    genClosure_MenuitemChildRemoved         ,
    mk_MenuitemChildRemovedCallback         ,
    noMenuitemChildRemovedCallback          ,
    onMenuitemChildRemoved                  ,
    wrap_MenuitemChildRemovedCallback       ,


-- ** event #signal:event#

    C_MenuitemEventCallback                 ,
    MenuitemEventCallback                   ,
#if defined(ENABLE_OVERLOADING)
    MenuitemEventSignalInfo                 ,
#endif
    afterMenuitemEvent                      ,
    genClosure_MenuitemEvent                ,
    mk_MenuitemEventCallback                ,
    noMenuitemEventCallback                 ,
    onMenuitemEvent                         ,
    wrap_MenuitemEventCallback              ,


-- ** itemActivated #signal:itemActivated#

    C_MenuitemItemActivatedCallback         ,
    MenuitemItemActivatedCallback           ,
#if defined(ENABLE_OVERLOADING)
    MenuitemItemActivatedSignalInfo         ,
#endif
    afterMenuitemItemActivated              ,
    genClosure_MenuitemItemActivated        ,
    mk_MenuitemItemActivatedCallback        ,
    noMenuitemItemActivatedCallback         ,
    onMenuitemItemActivated                 ,
    wrap_MenuitemItemActivatedCallback      ,


-- ** propertyChanged #signal:propertyChanged#

    C_MenuitemPropertyChangedCallback       ,
    MenuitemPropertyChangedCallback         ,
#if defined(ENABLE_OVERLOADING)
    MenuitemPropertyChangedSignalInfo       ,
#endif
    afterMenuitemPropertyChanged            ,
    genClosure_MenuitemPropertyChanged      ,
    mk_MenuitemPropertyChangedCallback      ,
    noMenuitemPropertyChangedCallback       ,
    onMenuitemPropertyChanged               ,
    wrap_MenuitemPropertyChangedCallback    ,


-- ** realized #signal:realized#

    C_MenuitemRealizedCallback              ,
    MenuitemRealizedCallback                ,
#if defined(ENABLE_OVERLOADING)
    MenuitemRealizedSignalInfo              ,
#endif
    afterMenuitemRealized                   ,
    genClosure_MenuitemRealized             ,
    mk_MenuitemRealizedCallback             ,
    noMenuitemRealizedCallback              ,
    onMenuitemRealized                      ,
    wrap_MenuitemRealizedCallback           ,


-- ** showToUser #signal:showToUser#

    C_MenuitemShowToUserCallback            ,
    MenuitemShowToUserCallback              ,
#if defined(ENABLE_OVERLOADING)
    MenuitemShowToUserSignalInfo            ,
#endif
    afterMenuitemShowToUser                 ,
    genClosure_MenuitemShowToUser           ,
    mk_MenuitemShowToUserCallback           ,
    noMenuitemShowToUserCallback            ,
    onMenuitemShowToUser                    ,
    wrap_MenuitemShowToUserCallback         ,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL

import qualified GI.GObject.Objects.Object as GObject.Object

-- | Memory-managed wrapper type.
newtype Menuitem = Menuitem (ManagedPtr Menuitem)
    deriving (Menuitem -> Menuitem -> Bool
(Menuitem -> Menuitem -> Bool)
-> (Menuitem -> Menuitem -> Bool) -> Eq Menuitem
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Menuitem -> Menuitem -> Bool
$c/= :: Menuitem -> Menuitem -> Bool
== :: Menuitem -> Menuitem -> Bool
$c== :: Menuitem -> Menuitem -> Bool
Eq)
foreign import ccall "dbusmenu_menuitem_get_type"
    c_dbusmenu_menuitem_get_type :: IO GType

instance GObject Menuitem where
    gobjectType :: IO GType
gobjectType = IO GType
c_dbusmenu_menuitem_get_type
    

-- | Convert 'Menuitem' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue Menuitem where
    toGValue :: Menuitem -> IO GValue
toGValue o :: Menuitem
o = do
        GType
gtype <- IO GType
c_dbusmenu_menuitem_get_type
        Menuitem -> (Ptr Menuitem -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Menuitem
o (GType
-> (GValue -> Ptr Menuitem -> IO ()) -> Ptr Menuitem -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr Menuitem -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO Menuitem
fromGValue gv :: GValue
gv = do
        Ptr Menuitem
ptr <- GValue -> IO (Ptr Menuitem)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr Menuitem)
        (ManagedPtr Menuitem -> Menuitem) -> Ptr Menuitem -> IO Menuitem
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Menuitem -> Menuitem
Menuitem Ptr Menuitem
ptr
        
    

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

instance O.HasParentTypes Menuitem
type instance O.ParentTypes Menuitem = '[GObject.Object.Object]

-- | Cast to `Menuitem`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toMenuitem :: (MonadIO m, IsMenuitem o) => o -> m Menuitem
toMenuitem :: o -> m Menuitem
toMenuitem = IO Menuitem -> m Menuitem
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Menuitem -> m Menuitem)
-> (o -> IO Menuitem) -> o -> m Menuitem
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Menuitem -> Menuitem) -> o -> IO Menuitem
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr Menuitem -> Menuitem
Menuitem

-- | A convenience alias for `Nothing` :: `Maybe` `Menuitem`.
noMenuitem :: Maybe Menuitem
noMenuitem :: Maybe Menuitem
noMenuitem = Maybe Menuitem
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveMenuitemMethod (t :: Symbol) (o :: *) :: * where
    ResolveMenuitemMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveMenuitemMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveMenuitemMethod "childAddPosition" o = MenuitemChildAddPositionMethodInfo
    ResolveMenuitemMethod "childAppend" o = MenuitemChildAppendMethodInfo
    ResolveMenuitemMethod "childDelete" o = MenuitemChildDeleteMethodInfo
    ResolveMenuitemMethod "childFind" o = MenuitemChildFindMethodInfo
    ResolveMenuitemMethod "childPrepend" o = MenuitemChildPrependMethodInfo
    ResolveMenuitemMethod "childReorder" o = MenuitemChildReorderMethodInfo
    ResolveMenuitemMethod "findId" o = MenuitemFindIdMethodInfo
    ResolveMenuitemMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveMenuitemMethod "foreach" o = MenuitemForeachMethodInfo
    ResolveMenuitemMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveMenuitemMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveMenuitemMethod "handleEvent" o = MenuitemHandleEventMethodInfo
    ResolveMenuitemMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveMenuitemMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveMenuitemMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveMenuitemMethod "propertiesCopy" o = MenuitemPropertiesCopyMethodInfo
    ResolveMenuitemMethod "propertiesList" o = MenuitemPropertiesListMethodInfo
    ResolveMenuitemMethod "propertyExist" o = MenuitemPropertyExistMethodInfo
    ResolveMenuitemMethod "propertyGet" o = MenuitemPropertyGetMethodInfo
    ResolveMenuitemMethod "propertyGetBool" o = MenuitemPropertyGetBoolMethodInfo
    ResolveMenuitemMethod "propertyGetByteArray" o = MenuitemPropertyGetByteArrayMethodInfo
    ResolveMenuitemMethod "propertyGetInt" o = MenuitemPropertyGetIntMethodInfo
    ResolveMenuitemMethod "propertyGetVariant" o = MenuitemPropertyGetVariantMethodInfo
    ResolveMenuitemMethod "propertyRemove" o = MenuitemPropertyRemoveMethodInfo
    ResolveMenuitemMethod "propertySet" o = MenuitemPropertySetMethodInfo
    ResolveMenuitemMethod "propertySetBool" o = MenuitemPropertySetBoolMethodInfo
    ResolveMenuitemMethod "propertySetByteArray" o = MenuitemPropertySetByteArrayMethodInfo
    ResolveMenuitemMethod "propertySetInt" o = MenuitemPropertySetIntMethodInfo
    ResolveMenuitemMethod "propertySetVariant" o = MenuitemPropertySetVariantMethodInfo
    ResolveMenuitemMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveMenuitemMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveMenuitemMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveMenuitemMethod "sendAboutToShow" o = MenuitemSendAboutToShowMethodInfo
    ResolveMenuitemMethod "showToUser" o = MenuitemShowToUserMethodInfo
    ResolveMenuitemMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveMenuitemMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveMenuitemMethod "takeChildren" o = MenuitemTakeChildrenMethodInfo
    ResolveMenuitemMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveMenuitemMethod "unparent" o = MenuitemUnparentMethodInfo
    ResolveMenuitemMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveMenuitemMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveMenuitemMethod "getChildren" o = MenuitemGetChildrenMethodInfo
    ResolveMenuitemMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveMenuitemMethod "getId" o = MenuitemGetIdMethodInfo
    ResolveMenuitemMethod "getParent" o = MenuitemGetParentMethodInfo
    ResolveMenuitemMethod "getPosition" o = MenuitemGetPositionMethodInfo
    ResolveMenuitemMethod "getPositionRealized" o = MenuitemGetPositionRealizedMethodInfo
    ResolveMenuitemMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveMenuitemMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveMenuitemMethod "getRoot" o = MenuitemGetRootMethodInfo
    ResolveMenuitemMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveMenuitemMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveMenuitemMethod "setParent" o = MenuitemSetParentMethodInfo
    ResolveMenuitemMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveMenuitemMethod "setRoot" o = MenuitemSetRootMethodInfo
    ResolveMenuitemMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveMenuitemMethod t Menuitem, O.MethodInfo info Menuitem p) => OL.IsLabel t (Menuitem -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif

-- signal Menuitem::about-to-show
-- | Emitted when the submenu for this item
-- 		is about to be shown
type MenuitemAboutToShowCallback =
    IO Bool

-- | A convenience synonym for @`Nothing` :: `Maybe` `MenuitemAboutToShowCallback`@.
noMenuitemAboutToShowCallback :: Maybe MenuitemAboutToShowCallback
noMenuitemAboutToShowCallback :: Maybe MenuitemAboutToShowCallback
noMenuitemAboutToShowCallback = Maybe MenuitemAboutToShowCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_MenuitemAboutToShowCallback =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO CInt

-- | Generate a function pointer callable from C code, from a `C_MenuitemAboutToShowCallback`.
foreign import ccall "wrapper"
    mk_MenuitemAboutToShowCallback :: C_MenuitemAboutToShowCallback -> IO (FunPtr C_MenuitemAboutToShowCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_MenuitemAboutToShow :: MonadIO m => MenuitemAboutToShowCallback -> m (GClosure C_MenuitemAboutToShowCallback)
genClosure_MenuitemAboutToShow :: MenuitemAboutToShowCallback
-> m (GClosure C_MenuitemAboutToShowCallback)
genClosure_MenuitemAboutToShow cb :: MenuitemAboutToShowCallback
cb = IO (GClosure C_MenuitemAboutToShowCallback)
-> m (GClosure C_MenuitemAboutToShowCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_MenuitemAboutToShowCallback)
 -> m (GClosure C_MenuitemAboutToShowCallback))
-> IO (GClosure C_MenuitemAboutToShowCallback)
-> m (GClosure C_MenuitemAboutToShowCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_MenuitemAboutToShowCallback
cb' = MenuitemAboutToShowCallback -> C_MenuitemAboutToShowCallback
wrap_MenuitemAboutToShowCallback MenuitemAboutToShowCallback
cb
    C_MenuitemAboutToShowCallback
-> IO (FunPtr C_MenuitemAboutToShowCallback)
mk_MenuitemAboutToShowCallback C_MenuitemAboutToShowCallback
cb' IO (FunPtr C_MenuitemAboutToShowCallback)
-> (FunPtr C_MenuitemAboutToShowCallback
    -> IO (GClosure C_MenuitemAboutToShowCallback))
-> IO (GClosure C_MenuitemAboutToShowCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_MenuitemAboutToShowCallback
-> IO (GClosure C_MenuitemAboutToShowCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `MenuitemAboutToShowCallback` into a `C_MenuitemAboutToShowCallback`.
wrap_MenuitemAboutToShowCallback ::
    MenuitemAboutToShowCallback ->
    C_MenuitemAboutToShowCallback
wrap_MenuitemAboutToShowCallback :: MenuitemAboutToShowCallback -> C_MenuitemAboutToShowCallback
wrap_MenuitemAboutToShowCallback _cb :: MenuitemAboutToShowCallback
_cb _ _ = do
    Bool
result <- MenuitemAboutToShowCallback
_cb 
    let result' :: CInt
result' = (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
result
    CInt -> IO CInt
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
result'


-- | Connect a signal handler for the [aboutToShow](#signal:aboutToShow) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' menuitem #aboutToShow callback
-- @
-- 
-- 
onMenuitemAboutToShow :: (IsMenuitem a, MonadIO m) => a -> MenuitemAboutToShowCallback -> m SignalHandlerId
onMenuitemAboutToShow :: a -> MenuitemAboutToShowCallback -> m SignalHandlerId
onMenuitemAboutToShow obj :: a
obj cb :: MenuitemAboutToShowCallback
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_MenuitemAboutToShowCallback
cb' = MenuitemAboutToShowCallback -> C_MenuitemAboutToShowCallback
wrap_MenuitemAboutToShowCallback MenuitemAboutToShowCallback
cb
    FunPtr C_MenuitemAboutToShowCallback
cb'' <- C_MenuitemAboutToShowCallback
-> IO (FunPtr C_MenuitemAboutToShowCallback)
mk_MenuitemAboutToShowCallback C_MenuitemAboutToShowCallback
cb'
    a
-> Text
-> FunPtr C_MenuitemAboutToShowCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "about-to-show" FunPtr C_MenuitemAboutToShowCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [aboutToShow](#signal:aboutToShow) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' menuitem #aboutToShow callback
-- @
-- 
-- 
afterMenuitemAboutToShow :: (IsMenuitem a, MonadIO m) => a -> MenuitemAboutToShowCallback -> m SignalHandlerId
afterMenuitemAboutToShow :: a -> MenuitemAboutToShowCallback -> m SignalHandlerId
afterMenuitemAboutToShow obj :: a
obj cb :: MenuitemAboutToShowCallback
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_MenuitemAboutToShowCallback
cb' = MenuitemAboutToShowCallback -> C_MenuitemAboutToShowCallback
wrap_MenuitemAboutToShowCallback MenuitemAboutToShowCallback
cb
    FunPtr C_MenuitemAboutToShowCallback
cb'' <- C_MenuitemAboutToShowCallback
-> IO (FunPtr C_MenuitemAboutToShowCallback)
mk_MenuitemAboutToShowCallback C_MenuitemAboutToShowCallback
cb'
    a
-> Text
-> FunPtr C_MenuitemAboutToShowCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "about-to-show" FunPtr C_MenuitemAboutToShowCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data MenuitemAboutToShowSignalInfo
instance SignalInfo MenuitemAboutToShowSignalInfo where
    type HaskellCallbackType MenuitemAboutToShowSignalInfo = MenuitemAboutToShowCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_MenuitemAboutToShowCallback cb
        cb'' <- mk_MenuitemAboutToShowCallback cb'
        connectSignalFunPtr obj "about-to-show" cb'' connectMode detail

#endif

-- signal Menuitem::child-added
-- | Signaled when the child menuitem has been added to
-- 		the parent.
type MenuitemChildAddedCallback =
    GObject.Object.Object
    -- ^ /@arg1@/: The t'GI.Dbusmenu.Objects.Menuitem.Menuitem' which is the child.
    -> Word32
    -- ^ /@arg2@/: The position that the child is being added in.
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `MenuitemChildAddedCallback`@.
noMenuitemChildAddedCallback :: Maybe MenuitemChildAddedCallback
noMenuitemChildAddedCallback :: Maybe MenuitemChildAddedCallback
noMenuitemChildAddedCallback = Maybe MenuitemChildAddedCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_MenuitemChildAddedCallback =
    Ptr () ->                               -- object
    Ptr GObject.Object.Object ->
    Word32 ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_MenuitemChildAddedCallback`.
foreign import ccall "wrapper"
    mk_MenuitemChildAddedCallback :: C_MenuitemChildAddedCallback -> IO (FunPtr C_MenuitemChildAddedCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_MenuitemChildAdded :: MonadIO m => MenuitemChildAddedCallback -> m (GClosure C_MenuitemChildAddedCallback)
genClosure_MenuitemChildAdded :: MenuitemChildAddedCallback
-> m (GClosure C_MenuitemChildAddedCallback)
genClosure_MenuitemChildAdded cb :: MenuitemChildAddedCallback
cb = IO (GClosure C_MenuitemChildAddedCallback)
-> m (GClosure C_MenuitemChildAddedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_MenuitemChildAddedCallback)
 -> m (GClosure C_MenuitemChildAddedCallback))
-> IO (GClosure C_MenuitemChildAddedCallback)
-> m (GClosure C_MenuitemChildAddedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_MenuitemChildAddedCallback
cb' = MenuitemChildAddedCallback -> C_MenuitemChildAddedCallback
wrap_MenuitemChildAddedCallback MenuitemChildAddedCallback
cb
    C_MenuitemChildAddedCallback
-> IO (FunPtr C_MenuitemChildAddedCallback)
mk_MenuitemChildAddedCallback C_MenuitemChildAddedCallback
cb' IO (FunPtr C_MenuitemChildAddedCallback)
-> (FunPtr C_MenuitemChildAddedCallback
    -> IO (GClosure C_MenuitemChildAddedCallback))
-> IO (GClosure C_MenuitemChildAddedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_MenuitemChildAddedCallback
-> IO (GClosure C_MenuitemChildAddedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `MenuitemChildAddedCallback` into a `C_MenuitemChildAddedCallback`.
wrap_MenuitemChildAddedCallback ::
    MenuitemChildAddedCallback ->
    C_MenuitemChildAddedCallback
wrap_MenuitemChildAddedCallback :: MenuitemChildAddedCallback -> C_MenuitemChildAddedCallback
wrap_MenuitemChildAddedCallback _cb :: MenuitemChildAddedCallback
_cb _ arg1 :: Ptr Object
arg1 arg2 :: Word32
arg2 _ = do
    Object
arg1' <- ((ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Object -> Object
GObject.Object.Object) Ptr Object
arg1
    MenuitemChildAddedCallback
_cb  Object
arg1' Word32
arg2


-- | Connect a signal handler for the [childAdded](#signal:childAdded) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' menuitem #childAdded callback
-- @
-- 
-- 
onMenuitemChildAdded :: (IsMenuitem a, MonadIO m) => a -> MenuitemChildAddedCallback -> m SignalHandlerId
onMenuitemChildAdded :: a -> MenuitemChildAddedCallback -> m SignalHandlerId
onMenuitemChildAdded obj :: a
obj cb :: MenuitemChildAddedCallback
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_MenuitemChildAddedCallback
cb' = MenuitemChildAddedCallback -> C_MenuitemChildAddedCallback
wrap_MenuitemChildAddedCallback MenuitemChildAddedCallback
cb
    FunPtr C_MenuitemChildAddedCallback
cb'' <- C_MenuitemChildAddedCallback
-> IO (FunPtr C_MenuitemChildAddedCallback)
mk_MenuitemChildAddedCallback C_MenuitemChildAddedCallback
cb'
    a
-> Text
-> FunPtr C_MenuitemChildAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "child-added" FunPtr C_MenuitemChildAddedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [childAdded](#signal:childAdded) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' menuitem #childAdded callback
-- @
-- 
-- 
afterMenuitemChildAdded :: (IsMenuitem a, MonadIO m) => a -> MenuitemChildAddedCallback -> m SignalHandlerId
afterMenuitemChildAdded :: a -> MenuitemChildAddedCallback -> m SignalHandlerId
afterMenuitemChildAdded obj :: a
obj cb :: MenuitemChildAddedCallback
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_MenuitemChildAddedCallback
cb' = MenuitemChildAddedCallback -> C_MenuitemChildAddedCallback
wrap_MenuitemChildAddedCallback MenuitemChildAddedCallback
cb
    FunPtr C_MenuitemChildAddedCallback
cb'' <- C_MenuitemChildAddedCallback
-> IO (FunPtr C_MenuitemChildAddedCallback)
mk_MenuitemChildAddedCallback C_MenuitemChildAddedCallback
cb'
    a
-> Text
-> FunPtr C_MenuitemChildAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "child-added" FunPtr C_MenuitemChildAddedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data MenuitemChildAddedSignalInfo
instance SignalInfo MenuitemChildAddedSignalInfo where
    type HaskellCallbackType MenuitemChildAddedSignalInfo = MenuitemChildAddedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_MenuitemChildAddedCallback cb
        cb'' <- mk_MenuitemChildAddedCallback cb'
        connectSignalFunPtr obj "child-added" cb'' connectMode detail

#endif

-- signal Menuitem::child-moved
-- | Signaled when the child menuitem has had its location
-- 		in the list change.
type MenuitemChildMovedCallback =
    GObject.Object.Object
    -- ^ /@arg1@/: The t'GI.Dbusmenu.Objects.Menuitem.Menuitem' which is the child.
    -> Word32
    -- ^ /@arg2@/: The position that the child is being moved to.
    -> Word32
    -- ^ /@arg3@/: The position that the child is was in.
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `MenuitemChildMovedCallback`@.
noMenuitemChildMovedCallback :: Maybe MenuitemChildMovedCallback
noMenuitemChildMovedCallback :: Maybe MenuitemChildMovedCallback
noMenuitemChildMovedCallback = Maybe MenuitemChildMovedCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_MenuitemChildMovedCallback =
    Ptr () ->                               -- object
    Ptr GObject.Object.Object ->
    Word32 ->
    Word32 ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_MenuitemChildMovedCallback`.
foreign import ccall "wrapper"
    mk_MenuitemChildMovedCallback :: C_MenuitemChildMovedCallback -> IO (FunPtr C_MenuitemChildMovedCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_MenuitemChildMoved :: MonadIO m => MenuitemChildMovedCallback -> m (GClosure C_MenuitemChildMovedCallback)
genClosure_MenuitemChildMoved :: MenuitemChildMovedCallback
-> m (GClosure C_MenuitemChildMovedCallback)
genClosure_MenuitemChildMoved cb :: MenuitemChildMovedCallback
cb = IO (GClosure C_MenuitemChildMovedCallback)
-> m (GClosure C_MenuitemChildMovedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_MenuitemChildMovedCallback)
 -> m (GClosure C_MenuitemChildMovedCallback))
-> IO (GClosure C_MenuitemChildMovedCallback)
-> m (GClosure C_MenuitemChildMovedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_MenuitemChildMovedCallback
cb' = MenuitemChildMovedCallback -> C_MenuitemChildMovedCallback
wrap_MenuitemChildMovedCallback MenuitemChildMovedCallback
cb
    C_MenuitemChildMovedCallback
-> IO (FunPtr C_MenuitemChildMovedCallback)
mk_MenuitemChildMovedCallback C_MenuitemChildMovedCallback
cb' IO (FunPtr C_MenuitemChildMovedCallback)
-> (FunPtr C_MenuitemChildMovedCallback
    -> IO (GClosure C_MenuitemChildMovedCallback))
-> IO (GClosure C_MenuitemChildMovedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_MenuitemChildMovedCallback
-> IO (GClosure C_MenuitemChildMovedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `MenuitemChildMovedCallback` into a `C_MenuitemChildMovedCallback`.
wrap_MenuitemChildMovedCallback ::
    MenuitemChildMovedCallback ->
    C_MenuitemChildMovedCallback
wrap_MenuitemChildMovedCallback :: MenuitemChildMovedCallback -> C_MenuitemChildMovedCallback
wrap_MenuitemChildMovedCallback _cb :: MenuitemChildMovedCallback
_cb _ arg1 :: Ptr Object
arg1 arg2 :: Word32
arg2 arg3 :: Word32
arg3 _ = do
    Object
arg1' <- ((ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Object -> Object
GObject.Object.Object) Ptr Object
arg1
    MenuitemChildMovedCallback
_cb  Object
arg1' Word32
arg2 Word32
arg3


-- | Connect a signal handler for the [childMoved](#signal:childMoved) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' menuitem #childMoved callback
-- @
-- 
-- 
onMenuitemChildMoved :: (IsMenuitem a, MonadIO m) => a -> MenuitemChildMovedCallback -> m SignalHandlerId
onMenuitemChildMoved :: a -> MenuitemChildMovedCallback -> m SignalHandlerId
onMenuitemChildMoved obj :: a
obj cb :: MenuitemChildMovedCallback
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_MenuitemChildMovedCallback
cb' = MenuitemChildMovedCallback -> C_MenuitemChildMovedCallback
wrap_MenuitemChildMovedCallback MenuitemChildMovedCallback
cb
    FunPtr C_MenuitemChildMovedCallback
cb'' <- C_MenuitemChildMovedCallback
-> IO (FunPtr C_MenuitemChildMovedCallback)
mk_MenuitemChildMovedCallback C_MenuitemChildMovedCallback
cb'
    a
-> Text
-> FunPtr C_MenuitemChildMovedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "child-moved" FunPtr C_MenuitemChildMovedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [childMoved](#signal:childMoved) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' menuitem #childMoved callback
-- @
-- 
-- 
afterMenuitemChildMoved :: (IsMenuitem a, MonadIO m) => a -> MenuitemChildMovedCallback -> m SignalHandlerId
afterMenuitemChildMoved :: a -> MenuitemChildMovedCallback -> m SignalHandlerId
afterMenuitemChildMoved obj :: a
obj cb :: MenuitemChildMovedCallback
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_MenuitemChildMovedCallback
cb' = MenuitemChildMovedCallback -> C_MenuitemChildMovedCallback
wrap_MenuitemChildMovedCallback MenuitemChildMovedCallback
cb
    FunPtr C_MenuitemChildMovedCallback
cb'' <- C_MenuitemChildMovedCallback
-> IO (FunPtr C_MenuitemChildMovedCallback)
mk_MenuitemChildMovedCallback C_MenuitemChildMovedCallback
cb'
    a
-> Text
-> FunPtr C_MenuitemChildMovedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "child-moved" FunPtr C_MenuitemChildMovedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data MenuitemChildMovedSignalInfo
instance SignalInfo MenuitemChildMovedSignalInfo where
    type HaskellCallbackType MenuitemChildMovedSignalInfo = MenuitemChildMovedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_MenuitemChildMovedCallback cb
        cb'' <- mk_MenuitemChildMovedCallback cb'
        connectSignalFunPtr obj "child-moved" cb'' connectMode detail

#endif

-- signal Menuitem::child-removed
-- | Signaled when the child menuitem has been requested to
-- 		be removed from the parent.  This signal is called when
-- 		it has been removed from the list but not yet had
-- 		@/g_object_unref/@ called on it.
type MenuitemChildRemovedCallback =
    GObject.Object.Object
    -- ^ /@arg1@/: The t'GI.Dbusmenu.Objects.Menuitem.Menuitem' which was the child.
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `MenuitemChildRemovedCallback`@.
noMenuitemChildRemovedCallback :: Maybe MenuitemChildRemovedCallback
noMenuitemChildRemovedCallback :: Maybe MenuitemChildRemovedCallback
noMenuitemChildRemovedCallback = Maybe MenuitemChildRemovedCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_MenuitemChildRemovedCallback =
    Ptr () ->                               -- object
    Ptr GObject.Object.Object ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_MenuitemChildRemovedCallback`.
foreign import ccall "wrapper"
    mk_MenuitemChildRemovedCallback :: C_MenuitemChildRemovedCallback -> IO (FunPtr C_MenuitemChildRemovedCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_MenuitemChildRemoved :: MonadIO m => MenuitemChildRemovedCallback -> m (GClosure C_MenuitemChildRemovedCallback)
genClosure_MenuitemChildRemoved :: MenuitemChildRemovedCallback
-> m (GClosure C_MenuitemChildRemovedCallback)
genClosure_MenuitemChildRemoved cb :: MenuitemChildRemovedCallback
cb = IO (GClosure C_MenuitemChildRemovedCallback)
-> m (GClosure C_MenuitemChildRemovedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_MenuitemChildRemovedCallback)
 -> m (GClosure C_MenuitemChildRemovedCallback))
-> IO (GClosure C_MenuitemChildRemovedCallback)
-> m (GClosure C_MenuitemChildRemovedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_MenuitemChildRemovedCallback
cb' = MenuitemChildRemovedCallback -> C_MenuitemChildRemovedCallback
wrap_MenuitemChildRemovedCallback MenuitemChildRemovedCallback
cb
    C_MenuitemChildRemovedCallback
-> IO (FunPtr C_MenuitemChildRemovedCallback)
mk_MenuitemChildRemovedCallback C_MenuitemChildRemovedCallback
cb' IO (FunPtr C_MenuitemChildRemovedCallback)
-> (FunPtr C_MenuitemChildRemovedCallback
    -> IO (GClosure C_MenuitemChildRemovedCallback))
-> IO (GClosure C_MenuitemChildRemovedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_MenuitemChildRemovedCallback
-> IO (GClosure C_MenuitemChildRemovedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `MenuitemChildRemovedCallback` into a `C_MenuitemChildRemovedCallback`.
wrap_MenuitemChildRemovedCallback ::
    MenuitemChildRemovedCallback ->
    C_MenuitemChildRemovedCallback
wrap_MenuitemChildRemovedCallback :: MenuitemChildRemovedCallback -> C_MenuitemChildRemovedCallback
wrap_MenuitemChildRemovedCallback _cb :: MenuitemChildRemovedCallback
_cb _ arg1 :: Ptr Object
arg1 _ = do
    Object
arg1' <- ((ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Object -> Object
GObject.Object.Object) Ptr Object
arg1
    MenuitemChildRemovedCallback
_cb  Object
arg1'


-- | Connect a signal handler for the [childRemoved](#signal:childRemoved) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' menuitem #childRemoved callback
-- @
-- 
-- 
onMenuitemChildRemoved :: (IsMenuitem a, MonadIO m) => a -> MenuitemChildRemovedCallback -> m SignalHandlerId
onMenuitemChildRemoved :: a -> MenuitemChildRemovedCallback -> m SignalHandlerId
onMenuitemChildRemoved obj :: a
obj cb :: MenuitemChildRemovedCallback
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_MenuitemChildRemovedCallback
cb' = MenuitemChildRemovedCallback -> C_MenuitemChildRemovedCallback
wrap_MenuitemChildRemovedCallback MenuitemChildRemovedCallback
cb
    FunPtr C_MenuitemChildRemovedCallback
cb'' <- C_MenuitemChildRemovedCallback
-> IO (FunPtr C_MenuitemChildRemovedCallback)
mk_MenuitemChildRemovedCallback C_MenuitemChildRemovedCallback
cb'
    a
-> Text
-> FunPtr C_MenuitemChildRemovedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "child-removed" FunPtr C_MenuitemChildRemovedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [childRemoved](#signal:childRemoved) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' menuitem #childRemoved callback
-- @
-- 
-- 
afterMenuitemChildRemoved :: (IsMenuitem a, MonadIO m) => a -> MenuitemChildRemovedCallback -> m SignalHandlerId
afterMenuitemChildRemoved :: a -> MenuitemChildRemovedCallback -> m SignalHandlerId
afterMenuitemChildRemoved obj :: a
obj cb :: MenuitemChildRemovedCallback
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_MenuitemChildRemovedCallback
cb' = MenuitemChildRemovedCallback -> C_MenuitemChildRemovedCallback
wrap_MenuitemChildRemovedCallback MenuitemChildRemovedCallback
cb
    FunPtr C_MenuitemChildRemovedCallback
cb'' <- C_MenuitemChildRemovedCallback
-> IO (FunPtr C_MenuitemChildRemovedCallback)
mk_MenuitemChildRemovedCallback C_MenuitemChildRemovedCallback
cb'
    a
-> Text
-> FunPtr C_MenuitemChildRemovedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "child-removed" FunPtr C_MenuitemChildRemovedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data MenuitemChildRemovedSignalInfo
instance SignalInfo MenuitemChildRemovedSignalInfo where
    type HaskellCallbackType MenuitemChildRemovedSignalInfo = MenuitemChildRemovedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_MenuitemChildRemovedCallback cb
        cb'' <- mk_MenuitemChildRemovedCallback cb'
        connectSignalFunPtr obj "child-removed" cb'' connectMode detail

#endif

-- signal Menuitem::event
-- | Emitted when an event is passed through.  The event is signalled
-- 		after handle_event is called.
type MenuitemEventCallback =
    T.Text
    -- ^ /@arg1@/: Name of the event
    -> GVariant
    -- ^ /@arg2@/: Information passed along with the event
    -> Word32
    -- ^ /@arg3@/: X11 timestamp of when the event happened
    -> IO Bool

-- | A convenience synonym for @`Nothing` :: `Maybe` `MenuitemEventCallback`@.
noMenuitemEventCallback :: Maybe MenuitemEventCallback
noMenuitemEventCallback :: Maybe MenuitemEventCallback
noMenuitemEventCallback = Maybe MenuitemEventCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_MenuitemEventCallback =
    Ptr () ->                               -- object
    CString ->
    Ptr GVariant ->
    Word32 ->
    Ptr () ->                               -- user_data
    IO CInt

-- | Generate a function pointer callable from C code, from a `C_MenuitemEventCallback`.
foreign import ccall "wrapper"
    mk_MenuitemEventCallback :: C_MenuitemEventCallback -> IO (FunPtr C_MenuitemEventCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_MenuitemEvent :: MonadIO m => MenuitemEventCallback -> m (GClosure C_MenuitemEventCallback)
genClosure_MenuitemEvent :: MenuitemEventCallback -> m (GClosure C_MenuitemEventCallback)
genClosure_MenuitemEvent cb :: MenuitemEventCallback
cb = IO (GClosure C_MenuitemEventCallback)
-> m (GClosure C_MenuitemEventCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_MenuitemEventCallback)
 -> m (GClosure C_MenuitemEventCallback))
-> IO (GClosure C_MenuitemEventCallback)
-> m (GClosure C_MenuitemEventCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_MenuitemEventCallback
cb' = MenuitemEventCallback -> C_MenuitemEventCallback
wrap_MenuitemEventCallback MenuitemEventCallback
cb
    C_MenuitemEventCallback -> IO (FunPtr C_MenuitemEventCallback)
mk_MenuitemEventCallback C_MenuitemEventCallback
cb' IO (FunPtr C_MenuitemEventCallback)
-> (FunPtr C_MenuitemEventCallback
    -> IO (GClosure C_MenuitemEventCallback))
-> IO (GClosure C_MenuitemEventCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_MenuitemEventCallback
-> IO (GClosure C_MenuitemEventCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `MenuitemEventCallback` into a `C_MenuitemEventCallback`.
wrap_MenuitemEventCallback ::
    MenuitemEventCallback ->
    C_MenuitemEventCallback
wrap_MenuitemEventCallback :: MenuitemEventCallback -> C_MenuitemEventCallback
wrap_MenuitemEventCallback _cb :: MenuitemEventCallback
_cb _ arg1 :: CString
arg1 arg2 :: Ptr GVariant
arg2 arg3 :: Word32
arg3 _ = do
    Text
arg1' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
arg1
    GVariant
arg2' <- Ptr GVariant -> IO GVariant
B.GVariant.newGVariantFromPtr Ptr GVariant
arg2
    Bool
result <- MenuitemEventCallback
_cb  Text
arg1' GVariant
arg2' Word32
arg3
    let result' :: CInt
result' = (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
result
    CInt -> IO CInt
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
result'


-- | Connect a signal handler for the [event](#signal:event) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' menuitem #event callback
-- @
-- 
-- This signal admits a optional parameter @detail@.
-- If it's not @Nothing@, we will connect to “@event::detail@” instead.
-- 
onMenuitemEvent :: (IsMenuitem a, MonadIO m) => a -> P.Maybe T.Text -> MenuitemEventCallback -> m SignalHandlerId
onMenuitemEvent :: a -> Maybe Text -> MenuitemEventCallback -> m SignalHandlerId
onMenuitemEvent obj :: a
obj detail :: Maybe Text
detail cb :: MenuitemEventCallback
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_MenuitemEventCallback
cb' = MenuitemEventCallback -> C_MenuitemEventCallback
wrap_MenuitemEventCallback MenuitemEventCallback
cb
    FunPtr C_MenuitemEventCallback
cb'' <- C_MenuitemEventCallback -> IO (FunPtr C_MenuitemEventCallback)
mk_MenuitemEventCallback C_MenuitemEventCallback
cb'
    a
-> Text
-> FunPtr C_MenuitemEventCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "event" FunPtr C_MenuitemEventCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
detail

-- | Connect a signal handler for the [event](#signal:event) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' menuitem #event callback
-- @
-- 
-- This signal admits a optional parameter @detail@.
-- If it's not @Nothing@, we will connect to “@event::detail@” instead.
-- 
afterMenuitemEvent :: (IsMenuitem a, MonadIO m) => a -> P.Maybe T.Text -> MenuitemEventCallback -> m SignalHandlerId
afterMenuitemEvent :: a -> Maybe Text -> MenuitemEventCallback -> m SignalHandlerId
afterMenuitemEvent obj :: a
obj detail :: Maybe Text
detail cb :: MenuitemEventCallback
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_MenuitemEventCallback
cb' = MenuitemEventCallback -> C_MenuitemEventCallback
wrap_MenuitemEventCallback MenuitemEventCallback
cb
    FunPtr C_MenuitemEventCallback
cb'' <- C_MenuitemEventCallback -> IO (FunPtr C_MenuitemEventCallback)
mk_MenuitemEventCallback C_MenuitemEventCallback
cb'
    a
-> Text
-> FunPtr C_MenuitemEventCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "event" FunPtr C_MenuitemEventCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
detail


#if defined(ENABLE_OVERLOADING)
data MenuitemEventSignalInfo
instance SignalInfo MenuitemEventSignalInfo where
    type HaskellCallbackType MenuitemEventSignalInfo = MenuitemEventCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_MenuitemEventCallback cb
        cb'' <- mk_MenuitemEventCallback cb'
        connectSignalFunPtr obj "event" cb'' connectMode detail

#endif

-- signal Menuitem::item-activated
-- | Emitted on the objects on the server side when
-- 		they are signaled on the client side.
type MenuitemItemActivatedCallback =
    Word32
    -- ^ /@arg1@/: The timestamp of when it was activated
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `MenuitemItemActivatedCallback`@.
noMenuitemItemActivatedCallback :: Maybe MenuitemItemActivatedCallback
noMenuitemItemActivatedCallback :: Maybe MenuitemItemActivatedCallback
noMenuitemItemActivatedCallback = Maybe MenuitemItemActivatedCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_MenuitemItemActivatedCallback =
    Ptr () ->                               -- object
    Word32 ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_MenuitemItemActivatedCallback`.
foreign import ccall "wrapper"
    mk_MenuitemItemActivatedCallback :: C_MenuitemItemActivatedCallback -> IO (FunPtr C_MenuitemItemActivatedCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_MenuitemItemActivated :: MonadIO m => MenuitemItemActivatedCallback -> m (GClosure C_MenuitemItemActivatedCallback)
genClosure_MenuitemItemActivated :: MenuitemItemActivatedCallback
-> m (GClosure C_MenuitemItemActivatedCallback)
genClosure_MenuitemItemActivated cb :: MenuitemItemActivatedCallback
cb = IO (GClosure C_MenuitemItemActivatedCallback)
-> m (GClosure C_MenuitemItemActivatedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_MenuitemItemActivatedCallback)
 -> m (GClosure C_MenuitemItemActivatedCallback))
-> IO (GClosure C_MenuitemItemActivatedCallback)
-> m (GClosure C_MenuitemItemActivatedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_MenuitemItemActivatedCallback
cb' = MenuitemItemActivatedCallback -> C_MenuitemItemActivatedCallback
wrap_MenuitemItemActivatedCallback MenuitemItemActivatedCallback
cb
    C_MenuitemItemActivatedCallback
-> IO (FunPtr C_MenuitemItemActivatedCallback)
mk_MenuitemItemActivatedCallback C_MenuitemItemActivatedCallback
cb' IO (FunPtr C_MenuitemItemActivatedCallback)
-> (FunPtr C_MenuitemItemActivatedCallback
    -> IO (GClosure C_MenuitemItemActivatedCallback))
-> IO (GClosure C_MenuitemItemActivatedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_MenuitemItemActivatedCallback
-> IO (GClosure C_MenuitemItemActivatedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `MenuitemItemActivatedCallback` into a `C_MenuitemItemActivatedCallback`.
wrap_MenuitemItemActivatedCallback ::
    MenuitemItemActivatedCallback ->
    C_MenuitemItemActivatedCallback
wrap_MenuitemItemActivatedCallback :: MenuitemItemActivatedCallback -> C_MenuitemItemActivatedCallback
wrap_MenuitemItemActivatedCallback _cb :: MenuitemItemActivatedCallback
_cb _ arg1 :: Word32
arg1 _ = do
    MenuitemItemActivatedCallback
_cb  Word32
arg1


-- | Connect a signal handler for the [itemActivated](#signal:itemActivated) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' menuitem #itemActivated callback
-- @
-- 
-- 
onMenuitemItemActivated :: (IsMenuitem a, MonadIO m) => a -> MenuitemItemActivatedCallback -> m SignalHandlerId
onMenuitemItemActivated :: a -> MenuitemItemActivatedCallback -> m SignalHandlerId
onMenuitemItemActivated obj :: a
obj cb :: MenuitemItemActivatedCallback
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_MenuitemItemActivatedCallback
cb' = MenuitemItemActivatedCallback -> C_MenuitemItemActivatedCallback
wrap_MenuitemItemActivatedCallback MenuitemItemActivatedCallback
cb
    FunPtr C_MenuitemItemActivatedCallback
cb'' <- C_MenuitemItemActivatedCallback
-> IO (FunPtr C_MenuitemItemActivatedCallback)
mk_MenuitemItemActivatedCallback C_MenuitemItemActivatedCallback
cb'
    a
-> Text
-> FunPtr C_MenuitemItemActivatedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "item-activated" FunPtr C_MenuitemItemActivatedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [itemActivated](#signal:itemActivated) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' menuitem #itemActivated callback
-- @
-- 
-- 
afterMenuitemItemActivated :: (IsMenuitem a, MonadIO m) => a -> MenuitemItemActivatedCallback -> m SignalHandlerId
afterMenuitemItemActivated :: a -> MenuitemItemActivatedCallback -> m SignalHandlerId
afterMenuitemItemActivated obj :: a
obj cb :: MenuitemItemActivatedCallback
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_MenuitemItemActivatedCallback
cb' = MenuitemItemActivatedCallback -> C_MenuitemItemActivatedCallback
wrap_MenuitemItemActivatedCallback MenuitemItemActivatedCallback
cb
    FunPtr C_MenuitemItemActivatedCallback
cb'' <- C_MenuitemItemActivatedCallback
-> IO (FunPtr C_MenuitemItemActivatedCallback)
mk_MenuitemItemActivatedCallback C_MenuitemItemActivatedCallback
cb'
    a
-> Text
-> FunPtr C_MenuitemItemActivatedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "item-activated" FunPtr C_MenuitemItemActivatedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data MenuitemItemActivatedSignalInfo
instance SignalInfo MenuitemItemActivatedSignalInfo where
    type HaskellCallbackType MenuitemItemActivatedSignalInfo = MenuitemItemActivatedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_MenuitemItemActivatedCallback cb
        cb'' <- mk_MenuitemItemActivatedCallback cb'
        connectSignalFunPtr obj "item-activated" cb'' connectMode detail

#endif

-- signal Menuitem::property-changed
-- | Emitted everytime a property on a menuitem is either
-- 		updated or added.
type MenuitemPropertyChangedCallback =
    T.Text
    -- ^ /@arg1@/: The name of the property that changed
    -> GVariant
    -- ^ /@arg2@/: The new value of the property
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `MenuitemPropertyChangedCallback`@.
noMenuitemPropertyChangedCallback :: Maybe MenuitemPropertyChangedCallback
noMenuitemPropertyChangedCallback :: Maybe MenuitemPropertyChangedCallback
noMenuitemPropertyChangedCallback = Maybe MenuitemPropertyChangedCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_MenuitemPropertyChangedCallback =
    Ptr () ->                               -- object
    CString ->
    Ptr GVariant ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_MenuitemPropertyChangedCallback`.
foreign import ccall "wrapper"
    mk_MenuitemPropertyChangedCallback :: C_MenuitemPropertyChangedCallback -> IO (FunPtr C_MenuitemPropertyChangedCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_MenuitemPropertyChanged :: MonadIO m => MenuitemPropertyChangedCallback -> m (GClosure C_MenuitemPropertyChangedCallback)
genClosure_MenuitemPropertyChanged :: MenuitemPropertyChangedCallback
-> m (GClosure C_MenuitemPropertyChangedCallback)
genClosure_MenuitemPropertyChanged cb :: MenuitemPropertyChangedCallback
cb = IO (GClosure C_MenuitemPropertyChangedCallback)
-> m (GClosure C_MenuitemPropertyChangedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_MenuitemPropertyChangedCallback)
 -> m (GClosure C_MenuitemPropertyChangedCallback))
-> IO (GClosure C_MenuitemPropertyChangedCallback)
-> m (GClosure C_MenuitemPropertyChangedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_MenuitemPropertyChangedCallback
cb' = MenuitemPropertyChangedCallback
-> C_MenuitemPropertyChangedCallback
wrap_MenuitemPropertyChangedCallback MenuitemPropertyChangedCallback
cb
    C_MenuitemPropertyChangedCallback
-> IO (FunPtr C_MenuitemPropertyChangedCallback)
mk_MenuitemPropertyChangedCallback C_MenuitemPropertyChangedCallback
cb' IO (FunPtr C_MenuitemPropertyChangedCallback)
-> (FunPtr C_MenuitemPropertyChangedCallback
    -> IO (GClosure C_MenuitemPropertyChangedCallback))
-> IO (GClosure C_MenuitemPropertyChangedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_MenuitemPropertyChangedCallback
-> IO (GClosure C_MenuitemPropertyChangedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `MenuitemPropertyChangedCallback` into a `C_MenuitemPropertyChangedCallback`.
wrap_MenuitemPropertyChangedCallback ::
    MenuitemPropertyChangedCallback ->
    C_MenuitemPropertyChangedCallback
wrap_MenuitemPropertyChangedCallback :: MenuitemPropertyChangedCallback
-> C_MenuitemPropertyChangedCallback
wrap_MenuitemPropertyChangedCallback _cb :: MenuitemPropertyChangedCallback
_cb _ arg1 :: CString
arg1 arg2 :: Ptr GVariant
arg2 _ = do
    Text
arg1' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
arg1
    GVariant
arg2' <- Ptr GVariant -> IO GVariant
B.GVariant.newGVariantFromPtr Ptr GVariant
arg2
    MenuitemPropertyChangedCallback
_cb  Text
arg1' GVariant
arg2'


-- | Connect a signal handler for the [propertyChanged](#signal:propertyChanged) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' menuitem #propertyChanged callback
-- @
-- 
-- 
onMenuitemPropertyChanged :: (IsMenuitem a, MonadIO m) => a -> MenuitemPropertyChangedCallback -> m SignalHandlerId
onMenuitemPropertyChanged :: a -> MenuitemPropertyChangedCallback -> m SignalHandlerId
onMenuitemPropertyChanged obj :: a
obj cb :: MenuitemPropertyChangedCallback
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_MenuitemPropertyChangedCallback
cb' = MenuitemPropertyChangedCallback
-> C_MenuitemPropertyChangedCallback
wrap_MenuitemPropertyChangedCallback MenuitemPropertyChangedCallback
cb
    FunPtr C_MenuitemPropertyChangedCallback
cb'' <- C_MenuitemPropertyChangedCallback
-> IO (FunPtr C_MenuitemPropertyChangedCallback)
mk_MenuitemPropertyChangedCallback C_MenuitemPropertyChangedCallback
cb'
    a
-> Text
-> FunPtr C_MenuitemPropertyChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "property-changed" FunPtr C_MenuitemPropertyChangedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [propertyChanged](#signal:propertyChanged) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' menuitem #propertyChanged callback
-- @
-- 
-- 
afterMenuitemPropertyChanged :: (IsMenuitem a, MonadIO m) => a -> MenuitemPropertyChangedCallback -> m SignalHandlerId
afterMenuitemPropertyChanged :: a -> MenuitemPropertyChangedCallback -> m SignalHandlerId
afterMenuitemPropertyChanged obj :: a
obj cb :: MenuitemPropertyChangedCallback
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_MenuitemPropertyChangedCallback
cb' = MenuitemPropertyChangedCallback
-> C_MenuitemPropertyChangedCallback
wrap_MenuitemPropertyChangedCallback MenuitemPropertyChangedCallback
cb
    FunPtr C_MenuitemPropertyChangedCallback
cb'' <- C_MenuitemPropertyChangedCallback
-> IO (FunPtr C_MenuitemPropertyChangedCallback)
mk_MenuitemPropertyChangedCallback C_MenuitemPropertyChangedCallback
cb'
    a
-> Text
-> FunPtr C_MenuitemPropertyChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "property-changed" FunPtr C_MenuitemPropertyChangedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data MenuitemPropertyChangedSignalInfo
instance SignalInfo MenuitemPropertyChangedSignalInfo where
    type HaskellCallbackType MenuitemPropertyChangedSignalInfo = MenuitemPropertyChangedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_MenuitemPropertyChangedCallback cb
        cb'' <- mk_MenuitemPropertyChangedCallback cb'
        connectSignalFunPtr obj "property-changed" cb'' connectMode detail

#endif

-- signal Menuitem::realized
-- | Emitted when the initial request for properties
-- 		is complete on the item.  If there is a type
-- 		handler configured for the \"type\" parameter
-- 		that will be executed before this is signaled.
type MenuitemRealizedCallback =
    IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `MenuitemRealizedCallback`@.
noMenuitemRealizedCallback :: Maybe MenuitemRealizedCallback
noMenuitemRealizedCallback :: Maybe (IO ())
noMenuitemRealizedCallback = Maybe (IO ())
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_MenuitemRealizedCallback =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_MenuitemRealizedCallback`.
foreign import ccall "wrapper"
    mk_MenuitemRealizedCallback :: C_MenuitemRealizedCallback -> IO (FunPtr C_MenuitemRealizedCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_MenuitemRealized :: MonadIO m => MenuitemRealizedCallback -> m (GClosure C_MenuitemRealizedCallback)
genClosure_MenuitemRealized :: IO () -> m (GClosure C_MenuitemRealizedCallback)
genClosure_MenuitemRealized cb :: IO ()
cb = IO (GClosure C_MenuitemRealizedCallback)
-> m (GClosure C_MenuitemRealizedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_MenuitemRealizedCallback)
 -> m (GClosure C_MenuitemRealizedCallback))
-> IO (GClosure C_MenuitemRealizedCallback)
-> m (GClosure C_MenuitemRealizedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_MenuitemRealizedCallback
cb' = IO () -> C_MenuitemRealizedCallback
wrap_MenuitemRealizedCallback IO ()
cb
    C_MenuitemRealizedCallback
-> IO (FunPtr C_MenuitemRealizedCallback)
mk_MenuitemRealizedCallback C_MenuitemRealizedCallback
cb' IO (FunPtr C_MenuitemRealizedCallback)
-> (FunPtr C_MenuitemRealizedCallback
    -> IO (GClosure C_MenuitemRealizedCallback))
-> IO (GClosure C_MenuitemRealizedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_MenuitemRealizedCallback
-> IO (GClosure C_MenuitemRealizedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `MenuitemRealizedCallback` into a `C_MenuitemRealizedCallback`.
wrap_MenuitemRealizedCallback ::
    MenuitemRealizedCallback ->
    C_MenuitemRealizedCallback
wrap_MenuitemRealizedCallback :: IO () -> C_MenuitemRealizedCallback
wrap_MenuitemRealizedCallback _cb :: IO ()
_cb _ _ = do
    IO ()
_cb 


-- | Connect a signal handler for the [realized](#signal:realized) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' menuitem #realized callback
-- @
-- 
-- 
onMenuitemRealized :: (IsMenuitem a, MonadIO m) => a -> MenuitemRealizedCallback -> m SignalHandlerId
onMenuitemRealized :: a -> IO () -> m SignalHandlerId
onMenuitemRealized obj :: a
obj cb :: 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_MenuitemRealizedCallback
cb' = IO () -> C_MenuitemRealizedCallback
wrap_MenuitemRealizedCallback IO ()
cb
    FunPtr C_MenuitemRealizedCallback
cb'' <- C_MenuitemRealizedCallback
-> IO (FunPtr C_MenuitemRealizedCallback)
mk_MenuitemRealizedCallback C_MenuitemRealizedCallback
cb'
    a
-> Text
-> FunPtr C_MenuitemRealizedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "realized" FunPtr C_MenuitemRealizedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [realized](#signal:realized) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' menuitem #realized callback
-- @
-- 
-- 
afterMenuitemRealized :: (IsMenuitem a, MonadIO m) => a -> MenuitemRealizedCallback -> m SignalHandlerId
afterMenuitemRealized :: a -> IO () -> m SignalHandlerId
afterMenuitemRealized obj :: a
obj cb :: 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_MenuitemRealizedCallback
cb' = IO () -> C_MenuitemRealizedCallback
wrap_MenuitemRealizedCallback IO ()
cb
    FunPtr C_MenuitemRealizedCallback
cb'' <- C_MenuitemRealizedCallback
-> IO (FunPtr C_MenuitemRealizedCallback)
mk_MenuitemRealizedCallback C_MenuitemRealizedCallback
cb'
    a
-> Text
-> FunPtr C_MenuitemRealizedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "realized" FunPtr C_MenuitemRealizedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data MenuitemRealizedSignalInfo
instance SignalInfo MenuitemRealizedSignalInfo where
    type HaskellCallbackType MenuitemRealizedSignalInfo = MenuitemRealizedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_MenuitemRealizedCallback cb
        cb'' <- mk_MenuitemRealizedCallback cb'
        connectSignalFunPtr obj "realized" cb'' connectMode detail

#endif

-- signal Menuitem::show-to-user
-- | Signaled when the application would like the visualization
-- 		of this menu item shown to the user.  This usually requires
-- 		going over the bus to get it done.
type MenuitemShowToUserCallback =
    Word32
    -- ^ /@arg1@/: Timestamp the event happened at
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `MenuitemShowToUserCallback`@.
noMenuitemShowToUserCallback :: Maybe MenuitemShowToUserCallback
noMenuitemShowToUserCallback :: Maybe MenuitemItemActivatedCallback
noMenuitemShowToUserCallback = Maybe MenuitemItemActivatedCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_MenuitemShowToUserCallback =
    Ptr () ->                               -- object
    Word32 ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_MenuitemShowToUserCallback`.
foreign import ccall "wrapper"
    mk_MenuitemShowToUserCallback :: C_MenuitemShowToUserCallback -> IO (FunPtr C_MenuitemShowToUserCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_MenuitemShowToUser :: MonadIO m => MenuitemShowToUserCallback -> m (GClosure C_MenuitemShowToUserCallback)
genClosure_MenuitemShowToUser :: MenuitemItemActivatedCallback
-> m (GClosure C_MenuitemItemActivatedCallback)
genClosure_MenuitemShowToUser cb :: MenuitemItemActivatedCallback
cb = IO (GClosure C_MenuitemItemActivatedCallback)
-> m (GClosure C_MenuitemItemActivatedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_MenuitemItemActivatedCallback)
 -> m (GClosure C_MenuitemItemActivatedCallback))
-> IO (GClosure C_MenuitemItemActivatedCallback)
-> m (GClosure C_MenuitemItemActivatedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_MenuitemItemActivatedCallback
cb' = MenuitemItemActivatedCallback -> C_MenuitemItemActivatedCallback
wrap_MenuitemShowToUserCallback MenuitemItemActivatedCallback
cb
    C_MenuitemItemActivatedCallback
-> IO (FunPtr C_MenuitemItemActivatedCallback)
mk_MenuitemShowToUserCallback C_MenuitemItemActivatedCallback
cb' IO (FunPtr C_MenuitemItemActivatedCallback)
-> (FunPtr C_MenuitemItemActivatedCallback
    -> IO (GClosure C_MenuitemItemActivatedCallback))
-> IO (GClosure C_MenuitemItemActivatedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_MenuitemItemActivatedCallback
-> IO (GClosure C_MenuitemItemActivatedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `MenuitemShowToUserCallback` into a `C_MenuitemShowToUserCallback`.
wrap_MenuitemShowToUserCallback ::
    MenuitemShowToUserCallback ->
    C_MenuitemShowToUserCallback
wrap_MenuitemShowToUserCallback :: MenuitemItemActivatedCallback -> C_MenuitemItemActivatedCallback
wrap_MenuitemShowToUserCallback _cb :: MenuitemItemActivatedCallback
_cb _ arg1 :: Word32
arg1 _ = do
    MenuitemItemActivatedCallback
_cb  Word32
arg1


-- | Connect a signal handler for the [showToUser](#signal:showToUser) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' menuitem #showToUser callback
-- @
-- 
-- 
onMenuitemShowToUser :: (IsMenuitem a, MonadIO m) => a -> MenuitemShowToUserCallback -> m SignalHandlerId
onMenuitemShowToUser :: a -> MenuitemItemActivatedCallback -> m SignalHandlerId
onMenuitemShowToUser obj :: a
obj cb :: MenuitemItemActivatedCallback
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_MenuitemItemActivatedCallback
cb' = MenuitemItemActivatedCallback -> C_MenuitemItemActivatedCallback
wrap_MenuitemShowToUserCallback MenuitemItemActivatedCallback
cb
    FunPtr C_MenuitemItemActivatedCallback
cb'' <- C_MenuitemItemActivatedCallback
-> IO (FunPtr C_MenuitemItemActivatedCallback)
mk_MenuitemShowToUserCallback C_MenuitemItemActivatedCallback
cb'
    a
-> Text
-> FunPtr C_MenuitemItemActivatedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "show-to-user" FunPtr C_MenuitemItemActivatedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [showToUser](#signal:showToUser) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' menuitem #showToUser callback
-- @
-- 
-- 
afterMenuitemShowToUser :: (IsMenuitem a, MonadIO m) => a -> MenuitemShowToUserCallback -> m SignalHandlerId
afterMenuitemShowToUser :: a -> MenuitemItemActivatedCallback -> m SignalHandlerId
afterMenuitemShowToUser obj :: a
obj cb :: MenuitemItemActivatedCallback
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_MenuitemItemActivatedCallback
cb' = MenuitemItemActivatedCallback -> C_MenuitemItemActivatedCallback
wrap_MenuitemShowToUserCallback MenuitemItemActivatedCallback
cb
    FunPtr C_MenuitemItemActivatedCallback
cb'' <- C_MenuitemItemActivatedCallback
-> IO (FunPtr C_MenuitemItemActivatedCallback)
mk_MenuitemShowToUserCallback C_MenuitemItemActivatedCallback
cb'
    a
-> Text
-> FunPtr C_MenuitemItemActivatedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "show-to-user" FunPtr C_MenuitemItemActivatedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data MenuitemShowToUserSignalInfo
instance SignalInfo MenuitemShowToUserSignalInfo where
    type HaskellCallbackType MenuitemShowToUserSignalInfo = MenuitemShowToUserCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_MenuitemShowToUserCallback cb
        cb'' <- mk_MenuitemShowToUserCallback cb'
        connectSignalFunPtr obj "show-to-user" cb'' connectMode detail

#endif

-- VVV Prop "id"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@id@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' menuitem #id
-- @
getMenuitemId :: (MonadIO m, IsMenuitem o) => o -> m Int32
getMenuitemId :: o -> m Int32
getMenuitemId obj :: o
obj = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj "id"

-- | Construct a `GValueConstruct` with valid value for the “@id@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructMenuitemId :: (IsMenuitem o) => Int32 -> IO (GValueConstruct o)
constructMenuitemId :: Int32 -> IO (GValueConstruct o)
constructMenuitemId val :: Int32
val = String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 "id" Int32
val

#if defined(ENABLE_OVERLOADING)
data MenuitemIdPropertyInfo
instance AttrInfo MenuitemIdPropertyInfo where
    type AttrAllowedOps MenuitemIdPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint MenuitemIdPropertyInfo = IsMenuitem
    type AttrSetTypeConstraint MenuitemIdPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint MenuitemIdPropertyInfo = (~) Int32
    type AttrTransferType MenuitemIdPropertyInfo = Int32
    type AttrGetType MenuitemIdPropertyInfo = Int32
    type AttrLabel MenuitemIdPropertyInfo = "id"
    type AttrOrigin MenuitemIdPropertyInfo = Menuitem
    attrGet = getMenuitemId
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructMenuitemId
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Menuitem
type instance O.AttributeList Menuitem = MenuitemAttributeList
type MenuitemAttributeList = ('[ '("id", MenuitemIdPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
menuitemId :: AttrLabelProxy "id"
menuitemId = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Menuitem = MenuitemSignalList
type MenuitemSignalList = ('[ '("aboutToShow", MenuitemAboutToShowSignalInfo), '("childAdded", MenuitemChildAddedSignalInfo), '("childMoved", MenuitemChildMovedSignalInfo), '("childRemoved", MenuitemChildRemovedSignalInfo), '("event", MenuitemEventSignalInfo), '("itemActivated", MenuitemItemActivatedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("propertyChanged", MenuitemPropertyChangedSignalInfo), '("realized", MenuitemRealizedSignalInfo), '("showToUser", MenuitemShowToUserSignalInfo)] :: [(Symbol, *)])

#endif

-- method Menuitem::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" })
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_menuitem_new" dbusmenu_menuitem_new :: 
    IO (Ptr Menuitem)

-- | Create a new t'GI.Dbusmenu.Objects.Menuitem.Menuitem' with all default values.
menuitemNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Menuitem
    -- ^ __Returns:__ A newly allocated t'GI.Dbusmenu.Objects.Menuitem.Menuitem'.
menuitemNew :: m Menuitem
menuitemNew  = IO Menuitem -> m Menuitem
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Menuitem -> m Menuitem) -> IO Menuitem -> m Menuitem
forall a b. (a -> b) -> a -> b
$ do
    Ptr Menuitem
result <- IO (Ptr Menuitem)
dbusmenu_menuitem_new
    Text -> Ptr Menuitem -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "menuitemNew" Ptr Menuitem
result
    Menuitem
result' <- ((ManagedPtr Menuitem -> Menuitem) -> Ptr Menuitem -> IO Menuitem
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Menuitem -> Menuitem
Menuitem) Ptr Menuitem
result
    Menuitem -> IO Menuitem
forall (m :: * -> *) a. Monad m => a -> m a
return Menuitem
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Menuitem::new_with_id
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "id"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "ID to use for this menuitem"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" })
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_menuitem_new_with_id" dbusmenu_menuitem_new_with_id :: 
    Int32 ->                                -- id : TBasicType TInt
    IO (Ptr Menuitem)

-- | This creates a blank t'GI.Dbusmenu.Objects.Menuitem.Menuitem' with a specific ID.
menuitemNewWithId ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Int32
    -- ^ /@id@/: ID to use for this menuitem
    -> m Menuitem
    -- ^ __Returns:__ A newly allocated t'GI.Dbusmenu.Objects.Menuitem.Menuitem'.
menuitemNewWithId :: Int32 -> m Menuitem
menuitemNewWithId id :: Int32
id = IO Menuitem -> m Menuitem
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Menuitem -> m Menuitem) -> IO Menuitem -> m Menuitem
forall a b. (a -> b) -> a -> b
$ do
    Ptr Menuitem
result <- Int32 -> IO (Ptr Menuitem)
dbusmenu_menuitem_new_with_id Int32
id
    Text -> Ptr Menuitem -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "menuitemNewWithId" Ptr Menuitem
result
    Menuitem
result' <- ((ManagedPtr Menuitem -> Menuitem) -> Ptr Menuitem -> IO Menuitem
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Menuitem -> Menuitem
Menuitem) Ptr Menuitem
result
    Menuitem -> IO Menuitem
forall (m :: * -> *) a. Monad m => a -> m a
return Menuitem
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Menuitem::child_add_position
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mi"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "The #DbusmenuMenuitem that we're adding the child @child to."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "child"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #DbusmenuMenuitem to make a child of @mi."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "position"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Where in @mi object's list of chidren @child should be placed."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_menuitem_child_add_position" dbusmenu_menuitem_child_add_position :: 
    Ptr Menuitem ->                         -- mi : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    Ptr Menuitem ->                         -- child : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    Word32 ->                               -- position : TBasicType TUInt
    IO CInt

-- | Puts /@child@/ in the list of children for /@mi@/ at the location
-- specified in /@position@/.  If there is not enough entires available
-- then /@child@/ will be placed at the end of the list.
menuitemChildAddPosition ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuitem a, IsMenuitem b) =>
    a
    -- ^ /@mi@/: The t'GI.Dbusmenu.Objects.Menuitem.Menuitem' that we\'re adding the child /@child@/ to.
    -> b
    -- ^ /@child@/: The t'GI.Dbusmenu.Objects.Menuitem.Menuitem' to make a child of /@mi@/.
    -> Word32
    -- ^ /@position@/: Where in /@mi@/ object\'s list of chidren /@child@/ should be placed.
    -> m Bool
    -- ^ __Returns:__ Whether /@child@/ was added successfully.
menuitemChildAddPosition :: a -> b -> Word32 -> m Bool
menuitemChildAddPosition mi :: a
mi child :: b
child position :: Word32
position = MenuitemAboutToShowCallback -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (MenuitemAboutToShowCallback -> m Bool)
-> MenuitemAboutToShowCallback -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Menuitem
mi' <- a -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mi
    Ptr Menuitem
child' <- b -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
child
    CInt
result <- Ptr Menuitem -> Ptr Menuitem -> Word32 -> IO CInt
dbusmenu_menuitem_child_add_position Ptr Menuitem
mi' Ptr Menuitem
child' Word32
position
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mi
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
child
    Bool -> MenuitemAboutToShowCallback
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data MenuitemChildAddPositionMethodInfo
instance (signature ~ (b -> Word32 -> m Bool), MonadIO m, IsMenuitem a, IsMenuitem b) => O.MethodInfo MenuitemChildAddPositionMethodInfo a signature where
    overloadedMethod = menuitemChildAddPosition

#endif

-- method Menuitem::child_append
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mi"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "The #DbusmenuMenuitem which will become a new parent"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "child"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #DbusmenMenuitem that will be a child"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_menuitem_child_append" dbusmenu_menuitem_child_append :: 
    Ptr Menuitem ->                         -- mi : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    Ptr Menuitem ->                         -- child : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    IO CInt

-- | This function adds /@child@/ to the list of children on /@mi@/ at
-- the end of that list.
menuitemChildAppend ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuitem a, IsMenuitem b) =>
    a
    -- ^ /@mi@/: The t'GI.Dbusmenu.Objects.Menuitem.Menuitem' which will become a new parent
    -> b
    -- ^ /@child@/: The @/DbusmenMenuitem/@ that will be a child
    -> m Bool
    -- ^ __Returns:__ Whether the child has been added successfully.
menuitemChildAppend :: a -> b -> m Bool
menuitemChildAppend mi :: a
mi child :: b
child = MenuitemAboutToShowCallback -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (MenuitemAboutToShowCallback -> m Bool)
-> MenuitemAboutToShowCallback -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Menuitem
mi' <- a -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mi
    Ptr Menuitem
child' <- b -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
child
    CInt
result <- Ptr Menuitem -> Ptr Menuitem -> IO CInt
dbusmenu_menuitem_child_append Ptr Menuitem
mi' Ptr Menuitem
child'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mi
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
child
    Bool -> MenuitemAboutToShowCallback
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data MenuitemChildAppendMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsMenuitem a, IsMenuitem b) => O.MethodInfo MenuitemChildAppendMethodInfo a signature where
    overloadedMethod = menuitemChildAppend

#endif

-- method Menuitem::child_delete
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mi"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "The #DbusmenuMenuitem which has @child as a child"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "child"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The child #DbusmenuMenuitem that you want to no longer\n    be a child of @mi."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_menuitem_child_delete" dbusmenu_menuitem_child_delete :: 
    Ptr Menuitem ->                         -- mi : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    Ptr Menuitem ->                         -- child : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    IO CInt

-- | This function removes /@child@/ from the children list of /@mi@/.  It does
-- not call @/g_object_unref/@ on /@child@/.
menuitemChildDelete ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuitem a, IsMenuitem b) =>
    a
    -- ^ /@mi@/: The t'GI.Dbusmenu.Objects.Menuitem.Menuitem' which has /@child@/ as a child
    -> b
    -- ^ /@child@/: The child t'GI.Dbusmenu.Objects.Menuitem.Menuitem' that you want to no longer
    --     be a child of /@mi@/.
    -> m Bool
    -- ^ __Returns:__ If we were able to delete /@child@/.
menuitemChildDelete :: a -> b -> m Bool
menuitemChildDelete mi :: a
mi child :: b
child = MenuitemAboutToShowCallback -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (MenuitemAboutToShowCallback -> m Bool)
-> MenuitemAboutToShowCallback -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Menuitem
mi' <- a -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mi
    Ptr Menuitem
child' <- b -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
child
    CInt
result <- Ptr Menuitem -> Ptr Menuitem -> IO CInt
dbusmenu_menuitem_child_delete Ptr Menuitem
mi' Ptr Menuitem
child'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mi
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
child
    Bool -> MenuitemAboutToShowCallback
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data MenuitemChildDeleteMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsMenuitem a, IsMenuitem b) => O.MethodInfo MenuitemChildDeleteMethodInfo a signature where
    overloadedMethod = menuitemChildDelete

#endif

-- method Menuitem::child_find
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mi"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "The #DbusmenuMenuitem who's children to look on"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "id"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The ID of the child that we're looking for."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" })
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_menuitem_child_find" dbusmenu_menuitem_child_find :: 
    Ptr Menuitem ->                         -- mi : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    Int32 ->                                -- id : TBasicType TInt
    IO (Ptr Menuitem)

-- | Search the children of /@mi@/ to find one with the ID of /@id@/.
-- If it doesn\'t exist then we return @/NULL/@.
menuitemChildFind ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuitem a) =>
    a
    -- ^ /@mi@/: The t'GI.Dbusmenu.Objects.Menuitem.Menuitem' who\'s children to look on
    -> Int32
    -- ^ /@id@/: The ID of the child that we\'re looking for.
    -> m Menuitem
    -- ^ __Returns:__ The menu item with the ID /@id@/ or @/NULL/@ if it
    --    can\'t be found.
menuitemChildFind :: a -> Int32 -> m Menuitem
menuitemChildFind mi :: a
mi id :: Int32
id = IO Menuitem -> m Menuitem
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Menuitem -> m Menuitem) -> IO Menuitem -> m Menuitem
forall a b. (a -> b) -> a -> b
$ do
    Ptr Menuitem
mi' <- a -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mi
    Ptr Menuitem
result <- Ptr Menuitem -> Int32 -> IO (Ptr Menuitem)
dbusmenu_menuitem_child_find Ptr Menuitem
mi' Int32
id
    Text -> Ptr Menuitem -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "menuitemChildFind" Ptr Menuitem
result
    Menuitem
result' <- ((ManagedPtr Menuitem -> Menuitem) -> Ptr Menuitem -> IO Menuitem
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Menuitem -> Menuitem
Menuitem) Ptr Menuitem
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mi
    Menuitem -> IO Menuitem
forall (m :: * -> *) a. Monad m => a -> m a
return Menuitem
result'

#if defined(ENABLE_OVERLOADING)
data MenuitemChildFindMethodInfo
instance (signature ~ (Int32 -> m Menuitem), MonadIO m, IsMenuitem a) => O.MethodInfo MenuitemChildFindMethodInfo a signature where
    overloadedMethod = menuitemChildFind

#endif

-- method Menuitem::child_prepend
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mi"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "The #DbusmenuMenuitem which will become a new parent"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "child"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #DbusmenMenuitem that will be a child"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_menuitem_child_prepend" dbusmenu_menuitem_child_prepend :: 
    Ptr Menuitem ->                         -- mi : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    Ptr Menuitem ->                         -- child : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    IO CInt

-- | This function adds /@child@/ to the list of children on /@mi@/ at
-- the beginning of that list.
menuitemChildPrepend ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuitem a, IsMenuitem b) =>
    a
    -- ^ /@mi@/: The t'GI.Dbusmenu.Objects.Menuitem.Menuitem' which will become a new parent
    -> b
    -- ^ /@child@/: The @/DbusmenMenuitem/@ that will be a child
    -> m Bool
    -- ^ __Returns:__ Whether the child has been added successfully.
menuitemChildPrepend :: a -> b -> m Bool
menuitemChildPrepend mi :: a
mi child :: b
child = MenuitemAboutToShowCallback -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (MenuitemAboutToShowCallback -> m Bool)
-> MenuitemAboutToShowCallback -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Menuitem
mi' <- a -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mi
    Ptr Menuitem
child' <- b -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
child
    CInt
result <- Ptr Menuitem -> Ptr Menuitem -> IO CInt
dbusmenu_menuitem_child_prepend Ptr Menuitem
mi' Ptr Menuitem
child'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mi
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
child
    Bool -> MenuitemAboutToShowCallback
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data MenuitemChildPrependMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsMenuitem a, IsMenuitem b) => O.MethodInfo MenuitemChildPrependMethodInfo a signature where
    overloadedMethod = menuitemChildPrepend

#endif

-- method Menuitem::child_reorder
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mi"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "The #DbusmenuMenuitem that has children needing realignment"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "child"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "The #DbusmenuMenuitem that is a child needing to be moved"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "position"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The position in the list to place it in"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_menuitem_child_reorder" dbusmenu_menuitem_child_reorder :: 
    Ptr Menuitem ->                         -- mi : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    Ptr Menuitem ->                         -- child : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    Word32 ->                               -- position : TBasicType TUInt
    IO CInt

-- | This function moves a child on the list of children.  It is
-- for a child that is already in the list, but simply needs a
-- new location.
menuitemChildReorder ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuitem a, IsMenuitem b) =>
    a
    -- ^ /@mi@/: The t'GI.Dbusmenu.Objects.Menuitem.Menuitem' that has children needing realignment
    -> b
    -- ^ /@child@/: The t'GI.Dbusmenu.Objects.Menuitem.Menuitem' that is a child needing to be moved
    -> Word32
    -- ^ /@position@/: The position in the list to place it in
    -> m Bool
    -- ^ __Returns:__ Whether the move was successful.
menuitemChildReorder :: a -> b -> Word32 -> m Bool
menuitemChildReorder mi :: a
mi child :: b
child position :: Word32
position = MenuitemAboutToShowCallback -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (MenuitemAboutToShowCallback -> m Bool)
-> MenuitemAboutToShowCallback -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Menuitem
mi' <- a -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mi
    Ptr Menuitem
child' <- b -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
child
    CInt
result <- Ptr Menuitem -> Ptr Menuitem -> Word32 -> IO CInt
dbusmenu_menuitem_child_reorder Ptr Menuitem
mi' Ptr Menuitem
child' Word32
position
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mi
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
child
    Bool -> MenuitemAboutToShowCallback
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data MenuitemChildReorderMethodInfo
instance (signature ~ (b -> Word32 -> m Bool), MonadIO m, IsMenuitem a, IsMenuitem b) => O.MethodInfo MenuitemChildReorderMethodInfo a signature where
    overloadedMethod = menuitemChildReorder

#endif

-- method Menuitem::find_id
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mi"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "#DbusmenuMenuitem at the top of the tree to search"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "id"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "ID of the #DbusmenuMenuitem to search for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" })
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_menuitem_find_id" dbusmenu_menuitem_find_id :: 
    Ptr Menuitem ->                         -- mi : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    Int32 ->                                -- id : TBasicType TInt
    IO (Ptr Menuitem)

-- | This function searchs the whole tree of children that
-- are attached to /@mi@/.  This could be quite a few nodes, all
-- the way down the tree.  It is a depth first search.
menuitemFindId ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuitem a) =>
    a
    -- ^ /@mi@/: t'GI.Dbusmenu.Objects.Menuitem.Menuitem' at the top of the tree to search
    -> Int32
    -- ^ /@id@/: ID of the t'GI.Dbusmenu.Objects.Menuitem.Menuitem' to search for
    -> m Menuitem
    -- ^ __Returns:__ The t'GI.Dbusmenu.Objects.Menuitem.Menuitem' with the ID of /@id@/
    -- 	or @/NULL/@ if there isn\'t such a menu item in the tree
    -- 	represented by /@mi@/.
menuitemFindId :: a -> Int32 -> m Menuitem
menuitemFindId mi :: a
mi id :: Int32
id = IO Menuitem -> m Menuitem
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Menuitem -> m Menuitem) -> IO Menuitem -> m Menuitem
forall a b. (a -> b) -> a -> b
$ do
    Ptr Menuitem
mi' <- a -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mi
    Ptr Menuitem
result <- Ptr Menuitem -> Int32 -> IO (Ptr Menuitem)
dbusmenu_menuitem_find_id Ptr Menuitem
mi' Int32
id
    Text -> Ptr Menuitem -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "menuitemFindId" Ptr Menuitem
result
    Menuitem
result' <- ((ManagedPtr Menuitem -> Menuitem) -> Ptr Menuitem -> IO Menuitem
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Menuitem -> Menuitem
Menuitem) Ptr Menuitem
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mi
    Menuitem -> IO Menuitem
forall (m :: * -> *) a. Monad m => a -> m a
return Menuitem
result'

#if defined(ENABLE_OVERLOADING)
data MenuitemFindIdMethodInfo
instance (signature ~ (Int32 -> m Menuitem), MonadIO m, IsMenuitem a) => O.MethodInfo MenuitemFindIdMethodInfo a signature where
    overloadedMethod = menuitemFindId

#endif

-- method Menuitem::foreach
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mi"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #DbusmenItem to start from"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "func"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Function to call on every node in the tree"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "User data to pass to the function"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_menuitem_foreach" dbusmenu_menuitem_foreach :: 
    Ptr Menuitem ->                         -- mi : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    Ptr () ->                               -- func : TBasicType TPtr
    Ptr () ->                               -- data : TBasicType TPtr
    IO ()

-- | This calls the function /@func@/ on this menu item and all
-- of the children of this item.  And their children.  And
-- their children.  And... you get the point.  It will get
-- called on the whole tree.
menuitemForeach ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuitem a) =>
    a
    -- ^ /@mi@/: The @/DbusmenItem/@ to start from
    -> Ptr ()
    -- ^ /@func@/: Function to call on every node in the tree
    -> Ptr ()
    -- ^ /@data@/: User data to pass to the function
    -> m ()
menuitemForeach :: a -> Ptr () -> Ptr () -> m ()
menuitemForeach mi :: a
mi func :: Ptr ()
func data_ :: Ptr ()
data_ = 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 Menuitem
mi' <- a -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mi
    Ptr Menuitem -> C_MenuitemRealizedCallback
dbusmenu_menuitem_foreach Ptr Menuitem
mi' Ptr ()
func Ptr ()
data_
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mi
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MenuitemForeachMethodInfo
instance (signature ~ (Ptr () -> Ptr () -> m ()), MonadIO m, IsMenuitem a) => O.MethodInfo MenuitemForeachMethodInfo a signature where
    overloadedMethod = menuitemForeach

#endif

-- method Menuitem::get_children
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mi"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #DbusmenuMenuitem to query."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TGList
--                  (TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }))
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_menuitem_get_children" dbusmenu_menuitem_get_children :: 
    Ptr Menuitem ->                         -- mi : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    IO (Ptr (GList (Ptr Menuitem)))

-- | Returns simply the list of children that this menu item
-- has.  The list is valid until another child related function
-- is called, where it might be changed.
menuitemGetChildren ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuitem a) =>
    a
    -- ^ /@mi@/: The t'GI.Dbusmenu.Objects.Menuitem.Menuitem' to query.
    -> m [Menuitem]
    -- ^ __Returns:__ A t'GI.GLib.Structs.List.List' of pointers to t'GI.Dbusmenu.Objects.Menuitem.Menuitem' objects.
menuitemGetChildren :: a -> m [Menuitem]
menuitemGetChildren mi :: a
mi = IO [Menuitem] -> m [Menuitem]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Menuitem] -> m [Menuitem]) -> IO [Menuitem] -> m [Menuitem]
forall a b. (a -> b) -> a -> b
$ do
    Ptr Menuitem
mi' <- a -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mi
    Ptr (GList (Ptr Menuitem))
result <- Ptr Menuitem -> IO (Ptr (GList (Ptr Menuitem)))
dbusmenu_menuitem_get_children Ptr Menuitem
mi'
    [Ptr Menuitem]
result' <- Ptr (GList (Ptr Menuitem)) -> IO [Ptr Menuitem]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr Menuitem))
result
    [Menuitem]
result'' <- (Ptr Menuitem -> IO Menuitem) -> [Ptr Menuitem] -> IO [Menuitem]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr Menuitem -> Menuitem) -> Ptr Menuitem -> IO Menuitem
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Menuitem -> Menuitem
Menuitem) [Ptr Menuitem]
result'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mi
    [Menuitem] -> IO [Menuitem]
forall (m :: * -> *) a. Monad m => a -> m a
return [Menuitem]
result''

#if defined(ENABLE_OVERLOADING)
data MenuitemGetChildrenMethodInfo
instance (signature ~ (m [Menuitem]), MonadIO m, IsMenuitem a) => O.MethodInfo MenuitemGetChildrenMethodInfo a signature where
    overloadedMethod = menuitemGetChildren

#endif

-- method Menuitem::get_id
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mi"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #DbusmenuMenuitem to query."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_menuitem_get_id" dbusmenu_menuitem_get_id :: 
    Ptr Menuitem ->                         -- mi : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    IO Int32

-- | Gets the unique ID for /@mi@/.
menuitemGetId ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuitem a) =>
    a
    -- ^ /@mi@/: The t'GI.Dbusmenu.Objects.Menuitem.Menuitem' to query.
    -> m Int32
    -- ^ __Returns:__ The ID of the /@mi@/.
menuitemGetId :: a -> m Int32
menuitemGetId mi :: a
mi = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Menuitem
mi' <- a -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mi
    Int32
result <- Ptr Menuitem -> IO Int32
dbusmenu_menuitem_get_id Ptr Menuitem
mi'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mi
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data MenuitemGetIdMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsMenuitem a) => O.MethodInfo MenuitemGetIdMethodInfo a signature where
    overloadedMethod = menuitemGetId

#endif

-- method Menuitem::get_parent
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mi"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "The #DbusmenuMenuitem for which to inspect the parent"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" })
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_menuitem_get_parent" dbusmenu_menuitem_get_parent :: 
    Ptr Menuitem ->                         -- mi : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    IO (Ptr Menuitem)

-- | This function looks up the parent of /@mi@/
menuitemGetParent ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuitem a) =>
    a
    -- ^ /@mi@/: The t'GI.Dbusmenu.Objects.Menuitem.Menuitem' for which to inspect the parent
    -> m Menuitem
    -- ^ __Returns:__ The parent of this menu item
menuitemGetParent :: a -> m Menuitem
menuitemGetParent mi :: a
mi = IO Menuitem -> m Menuitem
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Menuitem -> m Menuitem) -> IO Menuitem -> m Menuitem
forall a b. (a -> b) -> a -> b
$ do
    Ptr Menuitem
mi' <- a -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mi
    Ptr Menuitem
result <- Ptr Menuitem -> IO (Ptr Menuitem)
dbusmenu_menuitem_get_parent Ptr Menuitem
mi'
    Text -> Ptr Menuitem -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "menuitemGetParent" Ptr Menuitem
result
    Menuitem
result' <- ((ManagedPtr Menuitem -> Menuitem) -> Ptr Menuitem -> IO Menuitem
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Menuitem -> Menuitem
Menuitem) Ptr Menuitem
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mi
    Menuitem -> IO Menuitem
forall (m :: * -> *) a. Monad m => a -> m a
return Menuitem
result'

#if defined(ENABLE_OVERLOADING)
data MenuitemGetParentMethodInfo
instance (signature ~ (m Menuitem), MonadIO m, IsMenuitem a) => O.MethodInfo MenuitemGetParentMethodInfo a signature where
    overloadedMethod = menuitemGetParent

#endif

-- method Menuitem::get_position
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mi"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #DbusmenuMenuitem to find the position of"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "parent"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "The #DbusmenuMenuitem who's children contain @mi"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_menuitem_get_position" dbusmenu_menuitem_get_position :: 
    Ptr Menuitem ->                         -- mi : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    Ptr Menuitem ->                         -- parent : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    IO Word32

-- | This function returns the position of the menu item /@mi@/
-- in the children of /@parent@/.  It will return zero if the
-- menu item can\'t be found.
menuitemGetPosition ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuitem a, IsMenuitem b) =>
    a
    -- ^ /@mi@/: The t'GI.Dbusmenu.Objects.Menuitem.Menuitem' to find the position of
    -> b
    -- ^ /@parent@/: The t'GI.Dbusmenu.Objects.Menuitem.Menuitem' who\'s children contain /@mi@/
    -> m Word32
    -- ^ __Returns:__ The position of /@mi@/ in the children of /@parent@/.
menuitemGetPosition :: a -> b -> m Word32
menuitemGetPosition mi :: a
mi parent :: b
parent = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Menuitem
mi' <- a -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mi
    Ptr Menuitem
parent' <- b -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
parent
    Word32
result <- Ptr Menuitem -> Ptr Menuitem -> IO Word32
dbusmenu_menuitem_get_position Ptr Menuitem
mi' Ptr Menuitem
parent'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mi
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
parent
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data MenuitemGetPositionMethodInfo
instance (signature ~ (b -> m Word32), MonadIO m, IsMenuitem a, IsMenuitem b) => O.MethodInfo MenuitemGetPositionMethodInfo a signature where
    overloadedMethod = menuitemGetPosition

#endif

-- method Menuitem::get_position_realized
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mi"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #DbusmenuMenuitem to find the position of"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "parent"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "The #DbusmenuMenuitem who's children contain @mi"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_menuitem_get_position_realized" dbusmenu_menuitem_get_position_realized :: 
    Ptr Menuitem ->                         -- mi : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    Ptr Menuitem ->                         -- parent : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    IO Word32

-- | This function is very similar to @/dbusmenu_menuitem_get_position/@
-- except that it only counts in the children that have been realized.
menuitemGetPositionRealized ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuitem a, IsMenuitem b) =>
    a
    -- ^ /@mi@/: The t'GI.Dbusmenu.Objects.Menuitem.Menuitem' to find the position of
    -> b
    -- ^ /@parent@/: The t'GI.Dbusmenu.Objects.Menuitem.Menuitem' who\'s children contain /@mi@/
    -> m Word32
    -- ^ __Returns:__ The position of /@mi@/ in the realized children of /@parent@/.
menuitemGetPositionRealized :: a -> b -> m Word32
menuitemGetPositionRealized mi :: a
mi parent :: b
parent = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Menuitem
mi' <- a -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mi
    Ptr Menuitem
parent' <- b -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
parent
    Word32
result <- Ptr Menuitem -> Ptr Menuitem -> IO Word32
dbusmenu_menuitem_get_position_realized Ptr Menuitem
mi' Ptr Menuitem
parent'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mi
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
parent
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data MenuitemGetPositionRealizedMethodInfo
instance (signature ~ (b -> m Word32), MonadIO m, IsMenuitem a, IsMenuitem b) => O.MethodInfo MenuitemGetPositionRealizedMethodInfo a signature where
    overloadedMethod = menuitemGetPositionRealized

#endif

-- method Menuitem::get_root
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mi"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "#DbusmenuMenuitem to see whether it's root"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_menuitem_get_root" dbusmenu_menuitem_get_root :: 
    Ptr Menuitem ->                         -- mi : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    IO CInt

-- | This function returns the internal value of whether this is a
-- root node or not.
menuitemGetRoot ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuitem a) =>
    a
    -- ^ /@mi@/: t'GI.Dbusmenu.Objects.Menuitem.Menuitem' to see whether it\'s root
    -> m Bool
    -- ^ __Returns:__ @/TRUE/@ if this is a root node
menuitemGetRoot :: a -> m Bool
menuitemGetRoot mi :: a
mi = MenuitemAboutToShowCallback -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (MenuitemAboutToShowCallback -> m Bool)
-> MenuitemAboutToShowCallback -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Menuitem
mi' <- a -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mi
    CInt
result <- Ptr Menuitem -> IO CInt
dbusmenu_menuitem_get_root Ptr Menuitem
mi'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mi
    Bool -> MenuitemAboutToShowCallback
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data MenuitemGetRootMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsMenuitem a) => O.MethodInfo MenuitemGetRootMethodInfo a signature where
    overloadedMethod = menuitemGetRoot

#endif

-- method Menuitem::handle_event
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mi"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #DbusmenuMenuitem to send the signal on."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The name of the signal"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "variant"
--           , argType = TVariant
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A value that could be set for the event"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "timestamp"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The timestamp of when the event happened"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_menuitem_handle_event" dbusmenu_menuitem_handle_event :: 
    Ptr Menuitem ->                         -- mi : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    CString ->                              -- name : TBasicType TUTF8
    Ptr GVariant ->                         -- variant : TVariant
    Word32 ->                               -- timestamp : TBasicType TUInt
    IO ()

-- | This function is called to create an event.  It is likely
-- to be overrided by subclasses.  The default menu item
-- will respond to the activate signal and do:
-- 
-- Emits the t'GI.Dbusmenu.Objects.Menuitem.Menuitem'::@/item-activate/@ signal on this
-- menu item.  Called by server objects when they get the
-- appropriate DBus signals from the client.
-- 
-- If you subclass this function you should really think
-- about calling the parent function unless you have a good
-- reason not to.
menuitemHandleEvent ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuitem a) =>
    a
    -- ^ /@mi@/: The t'GI.Dbusmenu.Objects.Menuitem.Menuitem' to send the signal on.
    -> T.Text
    -- ^ /@name@/: The name of the signal
    -> GVariant
    -- ^ /@variant@/: A value that could be set for the event
    -> Word32
    -- ^ /@timestamp@/: The timestamp of when the event happened
    -> m ()
menuitemHandleEvent :: a -> Text -> GVariant -> Word32 -> m ()
menuitemHandleEvent mi :: a
mi name :: Text
name variant :: GVariant
variant timestamp :: Word32
timestamp = 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 Menuitem
mi' <- a -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mi
    CString
name' <- Text -> IO CString
textToCString Text
name
    Ptr GVariant
variant' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
variant
    Ptr Menuitem
-> CString -> Ptr GVariant -> MenuitemItemActivatedCallback
dbusmenu_menuitem_handle_event Ptr Menuitem
mi' CString
name' Ptr GVariant
variant' Word32
timestamp
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mi
    GVariant -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GVariant
variant
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MenuitemHandleEventMethodInfo
instance (signature ~ (T.Text -> GVariant -> Word32 -> m ()), MonadIO m, IsMenuitem a) => O.MethodInfo MenuitemHandleEventMethodInfo a signature where
    overloadedMethod = menuitemHandleEvent

#endif

-- method Menuitem::properties_copy
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mi"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "#DbusmenuMenuitem that we're interested in the properties of"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TGHash (TBasicType TPtr) (TBasicType TPtr))
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_menuitem_properties_copy" dbusmenu_menuitem_properties_copy :: 
    Ptr Menuitem ->                         -- mi : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    IO (Ptr (GHashTable (Ptr ()) (Ptr ())))

-- | This function takes the properties of a t'GI.Dbusmenu.Objects.Menuitem.Menuitem'
-- and puts them into a t'GI.GLib.Structs.HashTable.HashTable' that is referenced by the
-- key of a string and has the value of a string.  The hash
-- table may not have any entries if there aren\'t any or there
-- is an error in processing.  It is the caller\'s responsibility
-- to destroy the created t'GI.GLib.Structs.HashTable.HashTable'.
menuitemPropertiesCopy ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuitem a) =>
    a
    -- ^ /@mi@/: t'GI.Dbusmenu.Objects.Menuitem.Menuitem' that we\'re interested in the properties of
    -> m (Map.Map (Ptr ()) (Ptr ()))
    -- ^ __Returns:__ A brand new t'GI.GLib.Structs.HashTable.HashTable' that contains all of
    --    theroperties that are on this t'GI.Dbusmenu.Objects.Menuitem.Menuitem' /@mi@/.
menuitemPropertiesCopy :: a -> m (Map (Ptr ()) (Ptr ()))
menuitemPropertiesCopy mi :: a
mi = IO (Map (Ptr ()) (Ptr ())) -> m (Map (Ptr ()) (Ptr ()))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Map (Ptr ()) (Ptr ())) -> m (Map (Ptr ()) (Ptr ())))
-> IO (Map (Ptr ()) (Ptr ())) -> m (Map (Ptr ()) (Ptr ()))
forall a b. (a -> b) -> a -> b
$ do
    Ptr Menuitem
mi' <- a -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mi
    Ptr (GHashTable (Ptr ()) (Ptr ()))
result <- Ptr Menuitem -> IO (Ptr (GHashTable (Ptr ()) (Ptr ())))
dbusmenu_menuitem_properties_copy Ptr Menuitem
mi'
    Text -> Ptr (GHashTable (Ptr ()) (Ptr ())) -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "menuitemPropertiesCopy" Ptr (GHashTable (Ptr ()) (Ptr ()))
result
    [(PtrWrapped (Ptr ()), PtrWrapped (Ptr ()))]
result' <- Ptr (GHashTable (Ptr ()) (Ptr ()))
-> IO [(PtrWrapped (Ptr ()), PtrWrapped (Ptr ()))]
forall a b.
Ptr (GHashTable a b) -> IO [(PtrWrapped a, PtrWrapped b)]
unpackGHashTable Ptr (GHashTable (Ptr ()) (Ptr ()))
result
    let result'' :: [(Ptr (), PtrWrapped (Ptr ()))]
result'' = (PtrWrapped (Ptr ()) -> Ptr ())
-> [(PtrWrapped (Ptr ()), PtrWrapped (Ptr ()))]
-> [(Ptr (), PtrWrapped (Ptr ()))]
forall a c b. (a -> c) -> [(a, b)] -> [(c, b)]
mapFirst PtrWrapped (Ptr ()) -> Ptr ()
forall a. PtrWrapped (Ptr a) -> Ptr a
ptrUnpackPtr [(PtrWrapped (Ptr ()), PtrWrapped (Ptr ()))]
result'
    let result''' :: [(Ptr (), Ptr ())]
result''' = (PtrWrapped (Ptr ()) -> Ptr ())
-> [(Ptr (), PtrWrapped (Ptr ()))] -> [(Ptr (), Ptr ())]
forall b c a. (b -> c) -> [(a, b)] -> [(a, c)]
mapSecond PtrWrapped (Ptr ()) -> Ptr ()
forall a. PtrWrapped (Ptr a) -> Ptr a
ptrUnpackPtr [(Ptr (), PtrWrapped (Ptr ()))]
result''
    let result'''' :: Map (Ptr ()) (Ptr ())
result'''' = [(Ptr (), Ptr ())] -> Map (Ptr ()) (Ptr ())
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(Ptr (), Ptr ())]
result'''
    Ptr (GHashTable (Ptr ()) (Ptr ())) -> IO ()
forall a b. Ptr (GHashTable a b) -> IO ()
unrefGHashTable Ptr (GHashTable (Ptr ()) (Ptr ()))
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mi
    Map (Ptr ()) (Ptr ()) -> IO (Map (Ptr ()) (Ptr ()))
forall (m :: * -> *) a. Monad m => a -> m a
return Map (Ptr ()) (Ptr ())
result''''

#if defined(ENABLE_OVERLOADING)
data MenuitemPropertiesCopyMethodInfo
instance (signature ~ (m (Map.Map (Ptr ()) (Ptr ()))), MonadIO m, IsMenuitem a) => O.MethodInfo MenuitemPropertiesCopyMethodInfo a signature where
    overloadedMethod = menuitemPropertiesCopy

#endif

-- method Menuitem::properties_list
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mi"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "#DbusmenuMenuitem to list the properties on"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TGList (TBasicType TUTF8))
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_menuitem_properties_list" dbusmenu_menuitem_properties_list :: 
    Ptr Menuitem ->                         -- mi : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    IO (Ptr (GList CString))

-- | This functiong gets a list of the names of all the properties
-- that are set on this menu item.  This data on the list is owned
-- by the menuitem but the list is not and should be freed using
-- @/g_list_free()/@ when the calling function is done with it.
menuitemPropertiesList ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuitem a) =>
    a
    -- ^ /@mi@/: t'GI.Dbusmenu.Objects.Menuitem.Menuitem' to list the properties on
    -> m [T.Text]
    -- ^ __Returns:__ A list of
    -- strings or NULL if there are none.
menuitemPropertiesList :: a -> m [Text]
menuitemPropertiesList mi :: a
mi = 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 Menuitem
mi' <- a -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mi
    Ptr (GList CString)
result <- Ptr Menuitem -> IO (Ptr (GList CString))
dbusmenu_menuitem_properties_list Ptr Menuitem
mi'
    [CString]
result' <- Ptr (GList CString) -> IO [CString]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList CString)
result
    [Text]
result'' <- (CString -> IO Text) -> [CString] -> IO [Text]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText [CString]
result'
    Ptr (GList CString) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList CString)
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mi
    [Text] -> IO [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result''

#if defined(ENABLE_OVERLOADING)
data MenuitemPropertiesListMethodInfo
instance (signature ~ (m [T.Text]), MonadIO m, IsMenuitem a) => O.MethodInfo MenuitemPropertiesListMethodInfo a signature where
    overloadedMethod = menuitemPropertiesList

#endif

-- method Menuitem::property_exist
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mi"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "The #DbusmenuMenuitem to look for the property on."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "property"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The property to look for."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_menuitem_property_exist" dbusmenu_menuitem_property_exist :: 
    Ptr Menuitem ->                         -- mi : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    CString ->                              -- property : TBasicType TUTF8
    IO CInt

-- | Checkes to see if a particular property exists on /@mi@/ and
-- returns @/TRUE/@ if so.
menuitemPropertyExist ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuitem a) =>
    a
    -- ^ /@mi@/: The t'GI.Dbusmenu.Objects.Menuitem.Menuitem' to look for the property on.
    -> T.Text
    -- ^ /@property@/: The property to look for.
    -> m Bool
    -- ^ __Returns:__ A boolean checking to see if the property is available
menuitemPropertyExist :: a -> Text -> m Bool
menuitemPropertyExist mi :: a
mi property :: Text
property = MenuitemAboutToShowCallback -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (MenuitemAboutToShowCallback -> m Bool)
-> MenuitemAboutToShowCallback -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Menuitem
mi' <- a -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mi
    CString
property' <- Text -> IO CString
textToCString Text
property
    CInt
result <- Ptr Menuitem -> CString -> IO CInt
dbusmenu_menuitem_property_exist Ptr Menuitem
mi' CString
property'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mi
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
property'
    Bool -> MenuitemAboutToShowCallback
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data MenuitemPropertyExistMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m, IsMenuitem a) => O.MethodInfo MenuitemPropertyExistMethodInfo a signature where
    overloadedMethod = menuitemPropertyExist

#endif

-- method Menuitem::property_get
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mi"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "The #DbusmenuMenuitem to look for the property on."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "property"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The property to grab."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_menuitem_property_get" dbusmenu_menuitem_property_get :: 
    Ptr Menuitem ->                         -- mi : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    CString ->                              -- property : TBasicType TUTF8
    IO CString

-- | Look up a property on /@mi@/ and return the value of it if
-- it exits.  @/NULL/@ will be returned if the property doesn\'t
-- exist.
menuitemPropertyGet ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuitem a) =>
    a
    -- ^ /@mi@/: The t'GI.Dbusmenu.Objects.Menuitem.Menuitem' to look for the property on.
    -> T.Text
    -- ^ /@property@/: The property to grab.
    -> m T.Text
    -- ^ __Returns:__ A string with the value of the property
    -- 	that shouldn\'t be free\'d.  Or @/NULL/@ if the property
    -- 	is not set or is not a string.
menuitemPropertyGet :: a -> Text -> m Text
menuitemPropertyGet mi :: a
mi property :: Text
property = 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 Menuitem
mi' <- a -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mi
    CString
property' <- Text -> IO CString
textToCString Text
property
    CString
result <- Ptr Menuitem -> CString -> IO CString
dbusmenu_menuitem_property_get Ptr Menuitem
mi' CString
property'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "menuitemPropertyGet" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mi
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
property'
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data MenuitemPropertyGetMethodInfo
instance (signature ~ (T.Text -> m T.Text), MonadIO m, IsMenuitem a) => O.MethodInfo MenuitemPropertyGetMethodInfo a signature where
    overloadedMethod = menuitemPropertyGet

#endif

-- method Menuitem::property_get_bool
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mi"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "The #DbusmenuMenuitem to look for the property on."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "property"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The property to grab."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_menuitem_property_get_bool" dbusmenu_menuitem_property_get_bool :: 
    Ptr Menuitem ->                         -- mi : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    CString ->                              -- property : TBasicType TUTF8
    IO CInt

-- | Look up a property on /@mi@/ and return the value of it if
-- it exits.  Returns @/FALSE/@ if the property doesn\'t exist.
menuitemPropertyGetBool ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuitem a) =>
    a
    -- ^ /@mi@/: The t'GI.Dbusmenu.Objects.Menuitem.Menuitem' to look for the property on.
    -> T.Text
    -- ^ /@property@/: The property to grab.
    -> m Bool
    -- ^ __Returns:__ The value of the property or @/FALSE/@.
menuitemPropertyGetBool :: a -> Text -> m Bool
menuitemPropertyGetBool mi :: a
mi property :: Text
property = MenuitemAboutToShowCallback -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (MenuitemAboutToShowCallback -> m Bool)
-> MenuitemAboutToShowCallback -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Menuitem
mi' <- a -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mi
    CString
property' <- Text -> IO CString
textToCString Text
property
    CInt
result <- Ptr Menuitem -> CString -> IO CInt
dbusmenu_menuitem_property_get_bool Ptr Menuitem
mi' CString
property'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mi
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
property'
    Bool -> MenuitemAboutToShowCallback
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data MenuitemPropertyGetBoolMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m, IsMenuitem a) => O.MethodInfo MenuitemPropertyGetBoolMethodInfo a signature where
    overloadedMethod = menuitemPropertyGetBool

#endif

-- method Menuitem::property_get_byte_array
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mi"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "The #DbusmenuMenuitem to look for the property on."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "property"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The property to grab."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "nelements"
--           , argType = TBasicType TUInt64
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "A pointer to the location to store the number of items (out)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "nelements"
--              , argType = TBasicType TUInt64
--              , direction = DirectionOut
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText =
--                        Just "A pointer to the location to store the number of items (out)"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferEverything
--              }
--          ]
-- returnType: Just (TCArray False (-1) 2 (TBasicType TUInt8))
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_menuitem_property_get_byte_array" dbusmenu_menuitem_property_get_byte_array :: 
    Ptr Menuitem ->                         -- mi : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    CString ->                              -- property : TBasicType TUTF8
    Ptr Word64 ->                           -- nelements : TBasicType TUInt64
    IO (Ptr Word8)

-- | Look up a property on /@mi@/ and return the value of it if
-- it exits.  @/NULL/@ will be returned if the property doesn\'t
-- exist.
menuitemPropertyGetByteArray ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuitem a) =>
    a
    -- ^ /@mi@/: The t'GI.Dbusmenu.Objects.Menuitem.Menuitem' to look for the property on.
    -> T.Text
    -- ^ /@property@/: The property to grab.
    -> m ByteString
    -- ^ __Returns:__ A byte array with the
    -- 	value of the property that shouldn\'t be free\'d.  Or @/NULL/@ if the property
    -- 	is not set or is not a byte array.
menuitemPropertyGetByteArray :: a -> Text -> m ByteString
menuitemPropertyGetByteArray mi :: a
mi property :: Text
property = IO ByteString -> m ByteString
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ByteString -> m ByteString) -> IO ByteString -> m ByteString
forall a b. (a -> b) -> a -> b
$ do
    Ptr Menuitem
mi' <- a -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mi
    CString
property' <- Text -> IO CString
textToCString Text
property
    Ptr Word64
nelements <- IO (Ptr Word64)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word64)
    Ptr Word8
result <- Ptr Menuitem -> CString -> Ptr Word64 -> IO (Ptr Word8)
dbusmenu_menuitem_property_get_byte_array Ptr Menuitem
mi' CString
property' Ptr Word64
nelements
    Word64
nelements' <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek Ptr Word64
nelements
    Text -> Ptr Word8 -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "menuitemPropertyGetByteArray" Ptr Word8
result
    ByteString
result' <- (Word64 -> Ptr Word8 -> IO ByteString
forall a. Integral a => a -> Ptr Word8 -> IO ByteString
unpackByteStringWithLength Word64
nelements') Ptr Word8
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mi
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
property'
    Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
nelements
    ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
result'

#if defined(ENABLE_OVERLOADING)
data MenuitemPropertyGetByteArrayMethodInfo
instance (signature ~ (T.Text -> m ByteString), MonadIO m, IsMenuitem a) => O.MethodInfo MenuitemPropertyGetByteArrayMethodInfo a signature where
    overloadedMethod = menuitemPropertyGetByteArray

#endif

-- method Menuitem::property_get_int
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mi"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "The #DbusmenuMenuitem to look for the property on."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "property"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The property to grab."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_menuitem_property_get_int" dbusmenu_menuitem_property_get_int :: 
    Ptr Menuitem ->                         -- mi : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    CString ->                              -- property : TBasicType TUTF8
    IO Int32

-- | Look up a property on /@mi@/ and return the value of it if
-- it exits.  Returns zero if the property doesn\'t exist.
menuitemPropertyGetInt ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuitem a) =>
    a
    -- ^ /@mi@/: The t'GI.Dbusmenu.Objects.Menuitem.Menuitem' to look for the property on.
    -> T.Text
    -- ^ /@property@/: The property to grab.
    -> m Int32
    -- ^ __Returns:__ The value of the property or zero.
menuitemPropertyGetInt :: a -> Text -> m Int32
menuitemPropertyGetInt mi :: a
mi property :: Text
property = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Menuitem
mi' <- a -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mi
    CString
property' <- Text -> IO CString
textToCString Text
property
    Int32
result <- Ptr Menuitem -> CString -> IO Int32
dbusmenu_menuitem_property_get_int Ptr Menuitem
mi' CString
property'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mi
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
property'
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data MenuitemPropertyGetIntMethodInfo
instance (signature ~ (T.Text -> m Int32), MonadIO m, IsMenuitem a) => O.MethodInfo MenuitemPropertyGetIntMethodInfo a signature where
    overloadedMethod = menuitemPropertyGetInt

#endif

-- method Menuitem::property_get_variant
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mi"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "The #DbusmenuMenuitem to look for the property on."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "property"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The property to grab."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just TVariant
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_menuitem_property_get_variant" dbusmenu_menuitem_property_get_variant :: 
    Ptr Menuitem ->                         -- mi : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    CString ->                              -- property : TBasicType TUTF8
    IO (Ptr GVariant)

-- | Look up a property on /@mi@/ and return the value of it if
-- it exits.  @/NULL/@ will be returned if the property doesn\'t
-- exist.
menuitemPropertyGetVariant ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuitem a) =>
    a
    -- ^ /@mi@/: The t'GI.Dbusmenu.Objects.Menuitem.Menuitem' to look for the property on.
    -> T.Text
    -- ^ /@property@/: The property to grab.
    -> m GVariant
    -- ^ __Returns:__ A GVariant for the property.
menuitemPropertyGetVariant :: a -> Text -> m GVariant
menuitemPropertyGetVariant mi :: a
mi property :: Text
property = IO GVariant -> m GVariant
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GVariant -> m GVariant) -> IO GVariant -> m GVariant
forall a b. (a -> b) -> a -> b
$ do
    Ptr Menuitem
mi' <- a -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mi
    CString
property' <- Text -> IO CString
textToCString Text
property
    Ptr GVariant
result <- Ptr Menuitem -> CString -> IO (Ptr GVariant)
dbusmenu_menuitem_property_get_variant Ptr Menuitem
mi' CString
property'
    Text -> Ptr GVariant -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "menuitemPropertyGetVariant" Ptr GVariant
result
    GVariant
result' <- Ptr GVariant -> IO GVariant
B.GVariant.newGVariantFromPtr Ptr GVariant
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mi
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
property'
    GVariant -> IO GVariant
forall (m :: * -> *) a. Monad m => a -> m a
return GVariant
result'

#if defined(ENABLE_OVERLOADING)
data MenuitemPropertyGetVariantMethodInfo
instance (signature ~ (T.Text -> m GVariant), MonadIO m, IsMenuitem a) => O.MethodInfo MenuitemPropertyGetVariantMethodInfo a signature where
    overloadedMethod = menuitemPropertyGetVariant

#endif

-- method Menuitem::property_remove
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mi"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "The #DbusmenuMenuitem to remove the property on."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "property"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The property to look for."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_menuitem_property_remove" dbusmenu_menuitem_property_remove :: 
    Ptr Menuitem ->                         -- mi : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    CString ->                              -- property : TBasicType TUTF8
    IO ()

-- | Removes a property from the menuitem.
menuitemPropertyRemove ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuitem a) =>
    a
    -- ^ /@mi@/: The t'GI.Dbusmenu.Objects.Menuitem.Menuitem' to remove the property on.
    -> T.Text
    -- ^ /@property@/: The property to look for.
    -> m ()
menuitemPropertyRemove :: a -> Text -> m ()
menuitemPropertyRemove mi :: a
mi property :: Text
property = 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 Menuitem
mi' <- a -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mi
    CString
property' <- Text -> IO CString
textToCString Text
property
    Ptr Menuitem -> CString -> IO ()
dbusmenu_menuitem_property_remove Ptr Menuitem
mi' CString
property'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mi
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
property'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MenuitemPropertyRemoveMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsMenuitem a) => O.MethodInfo MenuitemPropertyRemoveMethodInfo a signature where
    overloadedMethod = menuitemPropertyRemove

#endif

-- method Menuitem::property_set
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mi"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #DbusmenuMenuitem to set the property on."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "property"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Name of the property to set."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The value of the property."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_menuitem_property_set" dbusmenu_menuitem_property_set :: 
    Ptr Menuitem ->                         -- mi : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    CString ->                              -- property : TBasicType TUTF8
    CString ->                              -- value : TBasicType TUTF8
    IO CInt

-- | Takes the pair of /@property@/ and /@value@/ and places them as a
-- property on /@mi@/.  If a property already exists by that name,
-- then the value is set to the new value.  If not, the property
-- is added.  If the value is changed or the property was previously
-- unset then the signal t'GI.Dbusmenu.Objects.Menuitem.Menuitem'::@/prop-changed/@ will be
-- emitted by this function.
menuitemPropertySet ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuitem a) =>
    a
    -- ^ /@mi@/: The t'GI.Dbusmenu.Objects.Menuitem.Menuitem' to set the property on.
    -> T.Text
    -- ^ /@property@/: Name of the property to set.
    -> T.Text
    -- ^ /@value@/: The value of the property.
    -> m Bool
    -- ^ __Returns:__ A boolean representing if the property value was set.
menuitemPropertySet :: a -> Text -> Text -> m Bool
menuitemPropertySet mi :: a
mi property :: Text
property value :: Text
value = MenuitemAboutToShowCallback -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (MenuitemAboutToShowCallback -> m Bool)
-> MenuitemAboutToShowCallback -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Menuitem
mi' <- a -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mi
    CString
property' <- Text -> IO CString
textToCString Text
property
    CString
value' <- Text -> IO CString
textToCString Text
value
    CInt
result <- Ptr Menuitem -> CString -> CString -> IO CInt
dbusmenu_menuitem_property_set Ptr Menuitem
mi' CString
property' CString
value'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mi
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
property'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
value'
    Bool -> MenuitemAboutToShowCallback
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data MenuitemPropertySetMethodInfo
instance (signature ~ (T.Text -> T.Text -> m Bool), MonadIO m, IsMenuitem a) => O.MethodInfo MenuitemPropertySetMethodInfo a signature where
    overloadedMethod = menuitemPropertySet

#endif

-- method Menuitem::property_set_bool
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mi"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #DbusmenuMenuitem to set the property on."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "property"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Name of the property to set."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The value of the property."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_menuitem_property_set_bool" dbusmenu_menuitem_property_set_bool :: 
    Ptr Menuitem ->                         -- mi : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    CString ->                              -- property : TBasicType TUTF8
    CInt ->                                 -- value : TBasicType TBoolean
    IO CInt

-- | Takes a boolean /@value@/ and sets it on /@property@/ as a
-- property on /@mi@/.  If a property already exists by that name,
-- then the value is set to the new value.  If not, the property
-- is added.  If the value is changed or the property was previously
-- unset then the signal t'GI.Dbusmenu.Objects.Menuitem.Menuitem'::@/prop-changed/@ will be
-- emitted by this function.
menuitemPropertySetBool ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuitem a) =>
    a
    -- ^ /@mi@/: The t'GI.Dbusmenu.Objects.Menuitem.Menuitem' to set the property on.
    -> T.Text
    -- ^ /@property@/: Name of the property to set.
    -> Bool
    -- ^ /@value@/: The value of the property.
    -> m Bool
    -- ^ __Returns:__ A boolean representing if the property value was set.
menuitemPropertySetBool :: a -> Text -> Bool -> m Bool
menuitemPropertySetBool mi :: a
mi property :: Text
property value :: Bool
value = MenuitemAboutToShowCallback -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (MenuitemAboutToShowCallback -> m Bool)
-> MenuitemAboutToShowCallback -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Menuitem
mi' <- a -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mi
    CString
property' <- Text -> IO CString
textToCString Text
property
    let value' :: CInt
value' = (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
value
    CInt
result <- Ptr Menuitem -> CString -> CInt -> IO CInt
dbusmenu_menuitem_property_set_bool Ptr Menuitem
mi' CString
property' CInt
value'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mi
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
property'
    Bool -> MenuitemAboutToShowCallback
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data MenuitemPropertySetBoolMethodInfo
instance (signature ~ (T.Text -> Bool -> m Bool), MonadIO m, IsMenuitem a) => O.MethodInfo MenuitemPropertySetBoolMethodInfo a signature where
    overloadedMethod = menuitemPropertySetBool

#endif

-- method Menuitem::property_set_byte_array
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mi"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #DbusmenuMenuitem to set the property on."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "property"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Name of the property to set."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TUInt8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The byte array." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "nelements"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The number of elements in the byte array."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_menuitem_property_set_byte_array" dbusmenu_menuitem_property_set_byte_array :: 
    Ptr Menuitem ->                         -- mi : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    CString ->                              -- property : TBasicType TUTF8
    Word8 ->                                -- value : TBasicType TUInt8
    Word64 ->                               -- nelements : TBasicType TUInt64
    IO CInt

-- | Takes a byte array /@value@/ and sets it on /@property@/ as a
-- property on /@mi@/.  If a property already exists by that name,
-- then the value is set to the new value.  If not, the property
-- is added.  If the value is changed or the property was previously
-- unset then the signal t'GI.Dbusmenu.Objects.Menuitem.Menuitem'::@/prop-changed/@ will be
-- emitted by this function.
menuitemPropertySetByteArray ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuitem a) =>
    a
    -- ^ /@mi@/: The t'GI.Dbusmenu.Objects.Menuitem.Menuitem' to set the property on.
    -> T.Text
    -- ^ /@property@/: Name of the property to set.
    -> Word8
    -- ^ /@value@/: The byte array.
    -> Word64
    -- ^ /@nelements@/: The number of elements in the byte array.
    -> m Bool
    -- ^ __Returns:__ A boolean representing if the property value was set.
menuitemPropertySetByteArray :: a -> Text -> Word8 -> Word64 -> m Bool
menuitemPropertySetByteArray mi :: a
mi property :: Text
property value :: Word8
value nelements :: Word64
nelements = MenuitemAboutToShowCallback -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (MenuitemAboutToShowCallback -> m Bool)
-> MenuitemAboutToShowCallback -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Menuitem
mi' <- a -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mi
    CString
property' <- Text -> IO CString
textToCString Text
property
    CInt
result <- Ptr Menuitem -> CString -> Word8 -> Word64 -> IO CInt
dbusmenu_menuitem_property_set_byte_array Ptr Menuitem
mi' CString
property' Word8
value Word64
nelements
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mi
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
property'
    Bool -> MenuitemAboutToShowCallback
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data MenuitemPropertySetByteArrayMethodInfo
instance (signature ~ (T.Text -> Word8 -> Word64 -> m Bool), MonadIO m, IsMenuitem a) => O.MethodInfo MenuitemPropertySetByteArrayMethodInfo a signature where
    overloadedMethod = menuitemPropertySetByteArray

#endif

-- method Menuitem::property_set_int
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mi"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #DbusmenuMenuitem to set the property on."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "property"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Name of the property to set."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The value of the property."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_menuitem_property_set_int" dbusmenu_menuitem_property_set_int :: 
    Ptr Menuitem ->                         -- mi : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    CString ->                              -- property : TBasicType TUTF8
    Int32 ->                                -- value : TBasicType TInt
    IO CInt

-- | Takes a boolean /@value@/ and sets it on /@property@/ as a
-- property on /@mi@/.  If a property already exists by that name,
-- then the value is set to the new value.  If not, the property
-- is added.  If the value is changed or the property was previously
-- unset then the signal t'GI.Dbusmenu.Objects.Menuitem.Menuitem'::@/prop-changed/@ will be
-- emitted by this function.
menuitemPropertySetInt ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuitem a) =>
    a
    -- ^ /@mi@/: The t'GI.Dbusmenu.Objects.Menuitem.Menuitem' to set the property on.
    -> T.Text
    -- ^ /@property@/: Name of the property to set.
    -> Int32
    -- ^ /@value@/: The value of the property.
    -> m Bool
    -- ^ __Returns:__ A boolean representing if the property value was set.
menuitemPropertySetInt :: a -> Text -> Int32 -> m Bool
menuitemPropertySetInt mi :: a
mi property :: Text
property value :: Int32
value = MenuitemAboutToShowCallback -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (MenuitemAboutToShowCallback -> m Bool)
-> MenuitemAboutToShowCallback -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Menuitem
mi' <- a -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mi
    CString
property' <- Text -> IO CString
textToCString Text
property
    CInt
result <- Ptr Menuitem -> CString -> Int32 -> IO CInt
dbusmenu_menuitem_property_set_int Ptr Menuitem
mi' CString
property' Int32
value
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mi
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
property'
    Bool -> MenuitemAboutToShowCallback
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data MenuitemPropertySetIntMethodInfo
instance (signature ~ (T.Text -> Int32 -> m Bool), MonadIO m, IsMenuitem a) => O.MethodInfo MenuitemPropertySetIntMethodInfo a signature where
    overloadedMethod = menuitemPropertySetInt

#endif

-- method Menuitem::property_set_variant
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mi"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #DbusmenuMenuitem to set the property on."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "property"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Name of the property to set."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TVariant
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The value of the property."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_menuitem_property_set_variant" dbusmenu_menuitem_property_set_variant :: 
    Ptr Menuitem ->                         -- mi : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    CString ->                              -- property : TBasicType TUTF8
    Ptr GVariant ->                         -- value : TVariant
    IO CInt

-- | Takes the pair of /@property@/ and /@value@/ and places them as a
-- property on /@mi@/.  If a property already exists by that name,
-- then the value is set to the new value.  If not, the property
-- is added.  If the value is changed or the property was previously
-- unset then the signal t'GI.Dbusmenu.Objects.Menuitem.Menuitem'::@/prop-changed/@ will be
-- emitted by this function.
menuitemPropertySetVariant ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuitem a) =>
    a
    -- ^ /@mi@/: The t'GI.Dbusmenu.Objects.Menuitem.Menuitem' to set the property on.
    -> T.Text
    -- ^ /@property@/: Name of the property to set.
    -> GVariant
    -- ^ /@value@/: The value of the property.
    -> m Bool
    -- ^ __Returns:__ A boolean representing if the property value was set.
menuitemPropertySetVariant :: a -> Text -> GVariant -> m Bool
menuitemPropertySetVariant mi :: a
mi property :: Text
property value :: GVariant
value = MenuitemAboutToShowCallback -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (MenuitemAboutToShowCallback -> m Bool)
-> MenuitemAboutToShowCallback -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Menuitem
mi' <- a -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mi
    CString
property' <- Text -> IO CString
textToCString Text
property
    Ptr GVariant
value' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
value
    CInt
result <- Ptr Menuitem -> CString -> Ptr GVariant -> IO CInt
dbusmenu_menuitem_property_set_variant Ptr Menuitem
mi' CString
property' Ptr GVariant
value'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mi
    GVariant -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GVariant
value
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
property'
    Bool -> MenuitemAboutToShowCallback
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data MenuitemPropertySetVariantMethodInfo
instance (signature ~ (T.Text -> GVariant -> m Bool), MonadIO m, IsMenuitem a) => O.MethodInfo MenuitemPropertySetVariantMethodInfo a signature where
    overloadedMethod = menuitemPropertySetVariant

#endif

-- method Menuitem::send_about_to_show
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mi"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #DbusmenuMenuitem to send the signal on."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cb"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Callback to call when the call has returned."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cb_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Data to pass to the callback."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_menuitem_send_about_to_show" dbusmenu_menuitem_send_about_to_show :: 
    Ptr Menuitem ->                         -- mi : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    Ptr () ->                               -- cb : TBasicType TPtr
    Ptr () ->                               -- cb_data : TBasicType TPtr
    IO ()

-- | This function is used to send the even that the submenu
-- of this item is about to be shown.  Callers to this event
-- should delay showing the menu until their callback is
-- called if possible.
menuitemSendAboutToShow ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuitem a) =>
    a
    -- ^ /@mi@/: The t'GI.Dbusmenu.Objects.Menuitem.Menuitem' to send the signal on.
    -> Ptr ()
    -- ^ /@cb@/: Callback to call when the call has returned.
    -> Ptr ()
    -- ^ /@cbData@/: Data to pass to the callback.
    -> m ()
menuitemSendAboutToShow :: a -> Ptr () -> Ptr () -> m ()
menuitemSendAboutToShow mi :: a
mi cb :: Ptr ()
cb cbData :: Ptr ()
cbData = 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 Menuitem
mi' <- a -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mi
    Ptr Menuitem -> C_MenuitemRealizedCallback
dbusmenu_menuitem_send_about_to_show Ptr Menuitem
mi' Ptr ()
cb Ptr ()
cbData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mi
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MenuitemSendAboutToShowMethodInfo
instance (signature ~ (Ptr () -> Ptr () -> m ()), MonadIO m, IsMenuitem a) => O.MethodInfo MenuitemSendAboutToShowMethodInfo a signature where
    overloadedMethod = menuitemSendAboutToShow

#endif

-- method Menuitem::set_parent
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mi"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "The #DbusmenuMenuitem for which to set the parent"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "parent"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The new parent #DbusmenuMenuitem"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_menuitem_set_parent" dbusmenu_menuitem_set_parent :: 
    Ptr Menuitem ->                         -- mi : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    Ptr Menuitem ->                         -- parent : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    IO CInt

-- | Sets the parent of /@mi@/ to /@parent@/. If /@mi@/ already
-- has a parent, then this call will fail. The parent will
-- be set automatically when using the usual methods to add a
-- child menuitem, so this function should not normally be
-- called directly
menuitemSetParent ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuitem a, IsMenuitem b) =>
    a
    -- ^ /@mi@/: The t'GI.Dbusmenu.Objects.Menuitem.Menuitem' for which to set the parent
    -> b
    -- ^ /@parent@/: The new parent t'GI.Dbusmenu.Objects.Menuitem.Menuitem'
    -> m Bool
    -- ^ __Returns:__ Whether the parent was set successfully
menuitemSetParent :: a -> b -> m Bool
menuitemSetParent mi :: a
mi parent :: b
parent = MenuitemAboutToShowCallback -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (MenuitemAboutToShowCallback -> m Bool)
-> MenuitemAboutToShowCallback -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Menuitem
mi' <- a -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mi
    Ptr Menuitem
parent' <- b -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
parent
    CInt
result <- Ptr Menuitem -> Ptr Menuitem -> IO CInt
dbusmenu_menuitem_set_parent Ptr Menuitem
mi' Ptr Menuitem
parent'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mi
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
parent
    Bool -> MenuitemAboutToShowCallback
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data MenuitemSetParentMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsMenuitem a, IsMenuitem b) => O.MethodInfo MenuitemSetParentMethodInfo a signature where
    overloadedMethod = menuitemSetParent

#endif

-- method Menuitem::set_root
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mi"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "#DbusmenuMenuitem to set whether it's root"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "root"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Whether @mi is a root node or not"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_menuitem_set_root" dbusmenu_menuitem_set_root :: 
    Ptr Menuitem ->                         -- mi : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    CInt ->                                 -- root : TBasicType TBoolean
    IO ()

-- | This function sets the internal value of whether this is a
-- root node or not.
menuitemSetRoot ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuitem a) =>
    a
    -- ^ /@mi@/: t'GI.Dbusmenu.Objects.Menuitem.Menuitem' to set whether it\'s root
    -> Bool
    -- ^ /@root@/: Whether /@mi@/ is a root node or not
    -> m ()
menuitemSetRoot :: a -> Bool -> m ()
menuitemSetRoot mi :: a
mi root :: Bool
root = 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 Menuitem
mi' <- a -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mi
    let root' :: CInt
root' = (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
root
    Ptr Menuitem -> CInt -> IO ()
dbusmenu_menuitem_set_root Ptr Menuitem
mi' CInt
root'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mi
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MenuitemSetRootMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsMenuitem a) => O.MethodInfo MenuitemSetRootMethodInfo a signature where
    overloadedMethod = menuitemSetRoot

#endif

-- method Menuitem::show_to_user
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mi"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "#DbusmenuMenuitem to show"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "timestamp"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "The time that the user requested it to be shown"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_menuitem_show_to_user" dbusmenu_menuitem_show_to_user :: 
    Ptr Menuitem ->                         -- mi : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    Word32 ->                               -- timestamp : TBasicType TUInt
    IO ()

-- | Signals that this menu item should be shown to the user.  If this is
-- server side the server will then take it and send it over the
-- bus.
menuitemShowToUser ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuitem a) =>
    a
    -- ^ /@mi@/: t'GI.Dbusmenu.Objects.Menuitem.Menuitem' to show
    -> Word32
    -- ^ /@timestamp@/: The time that the user requested it to be shown
    -> m ()
menuitemShowToUser :: a -> Word32 -> m ()
menuitemShowToUser mi :: a
mi timestamp :: Word32
timestamp = 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 Menuitem
mi' <- a -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mi
    Ptr Menuitem -> MenuitemItemActivatedCallback
dbusmenu_menuitem_show_to_user Ptr Menuitem
mi' Word32
timestamp
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mi
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MenuitemShowToUserMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsMenuitem a) => O.MethodInfo MenuitemShowToUserMethodInfo a signature where
    overloadedMethod = menuitemShowToUser

#endif

-- method Menuitem::take_children
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mi"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "The #DbusmenMenuitem to take the children from."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TGList
--                  (TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }))
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_menuitem_take_children" dbusmenu_menuitem_take_children :: 
    Ptr Menuitem ->                         -- mi : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    IO (Ptr (GList (Ptr Menuitem)))

-- | While the name sounds devious that\'s exactly what this function
-- does.  It takes the list of children from the /@mi@/ and clears the
-- internal list.  The calling function is now in charge of the ref\'s
-- on the children it has taken.  A lot of responsibility involved
-- in taking children.
menuitemTakeChildren ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuitem a) =>
    a
    -- ^ /@mi@/: The @/DbusmenMenuitem/@ to take the children from.
    -> m [Menuitem]
    -- ^ __Returns:__ 
    --    A t'GI.GLib.Structs.List.List' of pointers to t'GI.Dbusmenu.Objects.Menuitem.Menuitem' objects.
menuitemTakeChildren :: a -> m [Menuitem]
menuitemTakeChildren mi :: a
mi = IO [Menuitem] -> m [Menuitem]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Menuitem] -> m [Menuitem]) -> IO [Menuitem] -> m [Menuitem]
forall a b. (a -> b) -> a -> b
$ do
    Ptr Menuitem
mi' <- a -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mi
    Ptr (GList (Ptr Menuitem))
result <- Ptr Menuitem -> IO (Ptr (GList (Ptr Menuitem)))
dbusmenu_menuitem_take_children Ptr Menuitem
mi'
    [Ptr Menuitem]
result' <- Ptr (GList (Ptr Menuitem)) -> IO [Ptr Menuitem]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr Menuitem))
result
    [Menuitem]
result'' <- (Ptr Menuitem -> IO Menuitem) -> [Ptr Menuitem] -> IO [Menuitem]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr Menuitem -> Menuitem) -> Ptr Menuitem -> IO Menuitem
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Menuitem -> Menuitem
Menuitem) [Ptr Menuitem]
result'
    Ptr (GList (Ptr Menuitem)) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList (Ptr Menuitem))
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mi
    [Menuitem] -> IO [Menuitem]
forall (m :: * -> *) a. Monad m => a -> m a
return [Menuitem]
result''

#if defined(ENABLE_OVERLOADING)
data MenuitemTakeChildrenMethodInfo
instance (signature ~ (m [Menuitem]), MonadIO m, IsMenuitem a) => O.MethodInfo MenuitemTakeChildrenMethodInfo a signature where
    overloadedMethod = menuitemTakeChildren

#endif

-- method Menuitem::unparent
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mi"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #DbusmenuMenuitem to unparent"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_menuitem_unparent" dbusmenu_menuitem_unparent :: 
    Ptr Menuitem ->                         -- mi : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    IO CInt

-- | Unparents the menu item /@mi@/. If /@mi@/ doesn\'t have a
-- parent, then this call will fail. The menuitem will
-- be unparented automatically when using the usual methods
-- to delete a child menuitem, so this function should not
-- normally be called directly
menuitemUnparent ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuitem a) =>
    a
    -- ^ /@mi@/: The t'GI.Dbusmenu.Objects.Menuitem.Menuitem' to unparent
    -> m Bool
    -- ^ __Returns:__ Whether the menu item was unparented successfully
menuitemUnparent :: a -> m Bool
menuitemUnparent mi :: a
mi = MenuitemAboutToShowCallback -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (MenuitemAboutToShowCallback -> m Bool)
-> MenuitemAboutToShowCallback -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Menuitem
mi' <- a -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mi
    CInt
result <- Ptr Menuitem -> IO CInt
dbusmenu_menuitem_unparent Ptr Menuitem
mi'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mi
    Bool -> MenuitemAboutToShowCallback
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data MenuitemUnparentMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsMenuitem a) => O.MethodInfo MenuitemUnparentMethodInfo a signature where
    overloadedMethod = menuitemUnparent

#endif