{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A subclass of t'GI.Dbusmenu.Objects.Client.Client' to add functionality with regarding
-- building GTK items out of the abstract tree.

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

module GI.DbusmenuGtk3.Objects.Client
    ( 

-- * Exported types
    Client(..)                              ,
    IsClient                                ,
    toClient                                ,
    noClient                                ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveClientMethod                     ,
#endif


-- ** getAccelGroup #method:getAccelGroup#

#if defined(ENABLE_OVERLOADING)
    ClientGetAccelGroupMethodInfo           ,
#endif
    clientGetAccelGroup                     ,


-- ** menuitemGet #method:menuitemGet#

#if defined(ENABLE_OVERLOADING)
    ClientMenuitemGetMethodInfo             ,
#endif
    clientMenuitemGet                       ,


-- ** menuitemGetSubmenu #method:menuitemGetSubmenu#

#if defined(ENABLE_OVERLOADING)
    ClientMenuitemGetSubmenuMethodInfo      ,
#endif
    clientMenuitemGetSubmenu                ,


-- ** new #method:new#

    clientNew                               ,


-- ** newitemBase #method:newitemBase#

#if defined(ENABLE_OVERLOADING)
    ClientNewitemBaseMethodInfo             ,
#endif
    clientNewitemBase                       ,


-- ** setAccelGroup #method:setAccelGroup#

#if defined(ENABLE_OVERLOADING)
    ClientSetAccelGroupMethodInfo           ,
#endif
    clientSetAccelGroup                     ,




    ) 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.Dbusmenu.Objects.Client as Dbusmenu.Client
import qualified GI.Dbusmenu.Objects.Menuitem as Dbusmenu.Menuitem
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gtk.Objects.AccelGroup as Gtk.AccelGroup
import qualified GI.Gtk.Objects.Menu as Gtk.Menu
import qualified GI.Gtk.Objects.MenuItem as Gtk.MenuItem

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

instance GObject Client where
    gobjectType :: IO GType
gobjectType = IO GType
c_dbusmenu_gtkclient_get_type
    

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

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

instance O.HasParentTypes Client
type instance O.ParentTypes Client = '[Dbusmenu.Client.Client, GObject.Object.Object]

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

-- | A convenience alias for `Nothing` :: `Maybe` `Client`.
noClient :: Maybe Client
noClient :: Maybe Client
noClient = Maybe Client
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveClientMethod (t :: Symbol) (o :: *) :: * where
    ResolveClientMethod "addTypeHandler" o = Dbusmenu.Client.ClientAddTypeHandlerMethodInfo
    ResolveClientMethod "addTypeHandlerFull" o = Dbusmenu.Client.ClientAddTypeHandlerFullMethodInfo
    ResolveClientMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveClientMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveClientMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveClientMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveClientMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveClientMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveClientMethod "menuitemGet" o = ClientMenuitemGetMethodInfo
    ResolveClientMethod "menuitemGetSubmenu" o = ClientMenuitemGetSubmenuMethodInfo
    ResolveClientMethod "newitemBase" o = ClientNewitemBaseMethodInfo
    ResolveClientMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveClientMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveClientMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveClientMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveClientMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveClientMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveClientMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveClientMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveClientMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveClientMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveClientMethod "getAccelGroup" o = ClientGetAccelGroupMethodInfo
    ResolveClientMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveClientMethod "getIconPaths" o = Dbusmenu.Client.ClientGetIconPathsMethodInfo
    ResolveClientMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveClientMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveClientMethod "getRoot" o = Dbusmenu.Client.ClientGetRootMethodInfo
    ResolveClientMethod "getStatus" o = Dbusmenu.Client.ClientGetStatusMethodInfo
    ResolveClientMethod "getTextDirection" o = Dbusmenu.Client.ClientGetTextDirectionMethodInfo
    ResolveClientMethod "setAccelGroup" o = ClientSetAccelGroupMethodInfo
    ResolveClientMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveClientMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveClientMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveClientMethod l o = O.MethodResolutionFailed l o

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

#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Client
type instance O.AttributeList Client = ClientAttributeList
type ClientAttributeList = ('[ '("dbusName", Dbusmenu.Client.ClientDbusNamePropertyInfo), '("dbusObject", Dbusmenu.Client.ClientDbusObjectPropertyInfo), '("groupEvents", Dbusmenu.Client.ClientGroupEventsPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Client = ClientSignalList
type ClientSignalList = ('[ '("eventResult", Dbusmenu.Client.ClientEventResultSignalInfo), '("iconThemeDirsChanged", Dbusmenu.Client.ClientIconThemeDirsChangedSignalInfo), '("itemActivate", Dbusmenu.Client.ClientItemActivateSignalInfo), '("layoutUpdated", Dbusmenu.Client.ClientLayoutUpdatedSignalInfo), '("newMenuitem", Dbusmenu.Client.ClientNewMenuitemSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("rootChanged", Dbusmenu.Client.ClientRootChangedSignalInfo)] :: [(Symbol, *)])

#endif

-- method Client::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "dbus_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Name of the #DbusmenuServer on DBus"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dbus_object"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Name of the object on the #DbusmenuServer"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "DbusmenuGtk3" , name = "Client" })
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_gtkclient_new" dbusmenu_gtkclient_new :: 
    CString ->                              -- dbus_name : TBasicType TUTF8
    CString ->                              -- dbus_object : TBasicType TUTF8
    IO (Ptr Client)

-- | Creates a new t'GI.DbusmenuGtk3.Objects.Client.Client' object and creates a t'GI.Dbusmenu.Objects.Client.Client'
-- that connects across DBus to a t'GI.Dbusmenu.Objects.Server.Server'.
clientNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@dbusName@/: Name of the t'GI.Dbusmenu.Objects.Server.Server' on DBus
    -> T.Text
    -- ^ /@dbusObject@/: Name of the object on the t'GI.Dbusmenu.Objects.Server.Server'
    -> m Client
    -- ^ __Returns:__ A new t'GI.DbusmenuGtk3.Objects.Client.Client' sync\'d with a server
clientNew :: Text -> Text -> m Client
clientNew dbusName :: Text
dbusName dbusObject :: Text
dbusObject = IO Client -> m Client
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Client -> m Client) -> IO Client -> m Client
forall a b. (a -> b) -> a -> b
$ do
    CString
dbusName' <- Text -> IO CString
textToCString Text
dbusName
    CString
dbusObject' <- Text -> IO CString
textToCString Text
dbusObject
    Ptr Client
result <- CString -> CString -> IO (Ptr Client)
dbusmenu_gtkclient_new CString
dbusName' CString
dbusObject'
    Text -> Ptr Client -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "clientNew" Ptr Client
result
    Client
result' <- ((ManagedPtr Client -> Client) -> Ptr Client -> IO Client
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Client -> Client
Client) Ptr Client
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
dbusName'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
dbusObject'
    Client -> IO Client
forall (m :: * -> *) a. Monad m => a -> m a
return Client
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Client::get_accel_group
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "client"
--           , argType =
--               TInterface Name { namespace = "DbusmenuGtk3" , name = "Client" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Client to query for an accelerator group"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "AccelGroup" })
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_gtkclient_get_accel_group" dbusmenu_gtkclient_get_accel_group :: 
    Ptr Client ->                           -- client : TInterface (Name {namespace = "DbusmenuGtk3", name = "Client"})
    IO (Ptr Gtk.AccelGroup.AccelGroup)

-- | Gets the accel group for this client.
clientGetAccelGroup ::
    (B.CallStack.HasCallStack, MonadIO m, IsClient a) =>
    a
    -- ^ /@client@/: Client to query for an accelerator group
    -> m Gtk.AccelGroup.AccelGroup
    -- ^ __Returns:__ Either a valid group or @/NULL/@ on error or
    -- 	none set.
clientGetAccelGroup :: a -> m AccelGroup
clientGetAccelGroup client :: a
client = IO AccelGroup -> m AccelGroup
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AccelGroup -> m AccelGroup) -> IO AccelGroup -> m AccelGroup
forall a b. (a -> b) -> a -> b
$ do
    Ptr Client
client' <- a -> IO (Ptr Client)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
client
    Ptr AccelGroup
result <- Ptr Client -> IO (Ptr AccelGroup)
dbusmenu_gtkclient_get_accel_group Ptr Client
client'
    Text -> Ptr AccelGroup -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "clientGetAccelGroup" Ptr AccelGroup
result
    AccelGroup
result' <- ((ManagedPtr AccelGroup -> AccelGroup)
-> Ptr AccelGroup -> IO AccelGroup
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr AccelGroup -> AccelGroup
Gtk.AccelGroup.AccelGroup) Ptr AccelGroup
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
client
    AccelGroup -> IO AccelGroup
forall (m :: * -> *) a. Monad m => a -> m a
return AccelGroup
result'

#if defined(ENABLE_OVERLOADING)
data ClientGetAccelGroupMethodInfo
instance (signature ~ (m Gtk.AccelGroup.AccelGroup), MonadIO m, IsClient a) => O.MethodInfo ClientGetAccelGroupMethodInfo a signature where
    overloadedMethod = clientGetAccelGroup

#endif

-- method Client::menuitem_get
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "client"
--           , argType =
--               TInterface Name { namespace = "DbusmenuGtk3" , name = "Client" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #DbusmenuGtkClient with the item in it."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "item"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "#DbusmenuMenuitem to get associated #GtkMenuItem on."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "MenuItem" })
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_gtkclient_menuitem_get" dbusmenu_gtkclient_menuitem_get :: 
    Ptr Client ->                           -- client : TInterface (Name {namespace = "DbusmenuGtk3", name = "Client"})
    Ptr Dbusmenu.Menuitem.Menuitem ->       -- item : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    IO (Ptr Gtk.MenuItem.MenuItem)

-- | This grabs the t'GI.Gtk.Objects.MenuItem.MenuItem' that is associated with the
-- t'GI.Dbusmenu.Objects.Menuitem.Menuitem'.
clientMenuitemGet ::
    (B.CallStack.HasCallStack, MonadIO m, IsClient a, Dbusmenu.Menuitem.IsMenuitem b) =>
    a
    -- ^ /@client@/: A t'GI.DbusmenuGtk3.Objects.Client.Client' with the item in it.
    -> b
    -- ^ /@item@/: t'GI.Dbusmenu.Objects.Menuitem.Menuitem' to get associated t'GI.Gtk.Objects.MenuItem.MenuItem' on.
    -> m Gtk.MenuItem.MenuItem
    -- ^ __Returns:__ The t'GI.Gtk.Objects.MenuItem.MenuItem' that can be played with.
clientMenuitemGet :: a -> b -> m MenuItem
clientMenuitemGet client :: a
client item :: b
item = 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 Client
client' <- a -> IO (Ptr Client)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
client
    Ptr Menuitem
item' <- b -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
item
    Ptr MenuItem
result <- Ptr Client -> Ptr Menuitem -> IO (Ptr MenuItem)
dbusmenu_gtkclient_menuitem_get Ptr Client
client' Ptr Menuitem
item'
    Text -> Ptr MenuItem -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "clientMenuitemGet" 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
Gtk.MenuItem.MenuItem) Ptr MenuItem
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
client
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
item
    MenuItem -> IO MenuItem
forall (m :: * -> *) a. Monad m => a -> m a
return MenuItem
result'

#if defined(ENABLE_OVERLOADING)
data ClientMenuitemGetMethodInfo
instance (signature ~ (b -> m Gtk.MenuItem.MenuItem), MonadIO m, IsClient a, Dbusmenu.Menuitem.IsMenuitem b) => O.MethodInfo ClientMenuitemGetMethodInfo a signature where
    overloadedMethod = clientMenuitemGet

#endif

-- method Client::menuitem_get_submenu
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "client"
--           , argType =
--               TInterface Name { namespace = "DbusmenuGtk3" , name = "Client" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #DbusmenuGtkClient with the item in it."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "item"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "#DbusmenuMenuitem to get associated #GtkMenu on."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Menu" })
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_gtkclient_menuitem_get_submenu" dbusmenu_gtkclient_menuitem_get_submenu :: 
    Ptr Client ->                           -- client : TInterface (Name {namespace = "DbusmenuGtk3", name = "Client"})
    Ptr Dbusmenu.Menuitem.Menuitem ->       -- item : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    IO (Ptr Gtk.Menu.Menu)

-- | This grabs the submenu associated with the menuitem.
clientMenuitemGetSubmenu ::
    (B.CallStack.HasCallStack, MonadIO m, IsClient a, Dbusmenu.Menuitem.IsMenuitem b) =>
    a
    -- ^ /@client@/: A t'GI.DbusmenuGtk3.Objects.Client.Client' with the item in it.
    -> b
    -- ^ /@item@/: t'GI.Dbusmenu.Objects.Menuitem.Menuitem' to get associated t'GI.Gtk.Objects.Menu.Menu' on.
    -> m Gtk.Menu.Menu
    -- ^ __Returns:__ The t'GI.Gtk.Objects.Menu.Menu' if there is one.
clientMenuitemGetSubmenu :: a -> b -> m Menu
clientMenuitemGetSubmenu client :: a
client item :: b
item = IO Menu -> m Menu
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Menu -> m Menu) -> IO Menu -> m Menu
forall a b. (a -> b) -> a -> b
$ do
    Ptr Client
client' <- a -> IO (Ptr Client)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
client
    Ptr Menuitem
item' <- b -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
item
    Ptr Menu
result <- Ptr Client -> Ptr Menuitem -> IO (Ptr Menu)
dbusmenu_gtkclient_menuitem_get_submenu Ptr Client
client' Ptr Menuitem
item'
    Text -> Ptr Menu -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "clientMenuitemGetSubmenu" Ptr Menu
result
    Menu
result' <- ((ManagedPtr Menu -> Menu) -> Ptr Menu -> IO Menu
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Menu -> Menu
Gtk.Menu.Menu) Ptr Menu
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
client
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
item
    Menu -> IO Menu
forall (m :: * -> *) a. Monad m => a -> m a
return Menu
result'

#if defined(ENABLE_OVERLOADING)
data ClientMenuitemGetSubmenuMethodInfo
instance (signature ~ (b -> m Gtk.Menu.Menu), MonadIO m, IsClient a, Dbusmenu.Menuitem.IsMenuitem b) => O.MethodInfo ClientMenuitemGetSubmenuMethodInfo a signature where
    overloadedMethod = clientMenuitemGetSubmenu

#endif

-- method Client::newitem_base
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "client"
--           , argType =
--               TInterface Name { namespace = "DbusmenuGtk3" , name = "Client" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "The client handling everything on this connection"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "item"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "Menuitem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "The #DbusmenuMenuitem to attach the GTK-isms to"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "gmi"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "MenuItem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GtkMenuItem representing the GTK world's view of this menuitem"
--                 , 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 parent #DbusmenuMenuitem"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_gtkclient_newitem_base" dbusmenu_gtkclient_newitem_base :: 
    Ptr Client ->                           -- client : TInterface (Name {namespace = "DbusmenuGtk3", name = "Client"})
    Ptr Dbusmenu.Menuitem.Menuitem ->       -- item : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    Ptr Gtk.MenuItem.MenuItem ->            -- gmi : TInterface (Name {namespace = "Gtk", name = "MenuItem"})
    Ptr Dbusmenu.Menuitem.Menuitem ->       -- parent : TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
    IO ()

-- | This function provides some of the basic connectivity for being in
-- the GTK world.  Things like visibility and sensitivity of the item are
-- handled here so that the subclasses don\'t have to.  If you\'re building
-- your on GTK menu item you can use this function to apply those basic
-- attributes so that you don\'t have to deal with them either.
-- 
-- This also handles passing the \"activate\" signal back to the
-- t'GI.Dbusmenu.Objects.Menuitem.Menuitem' side of thing.
clientNewitemBase ::
    (B.CallStack.HasCallStack, MonadIO m, IsClient a, Dbusmenu.Menuitem.IsMenuitem b, Gtk.MenuItem.IsMenuItem c, Dbusmenu.Menuitem.IsMenuitem d) =>
    a
    -- ^ /@client@/: The client handling everything on this connection
    -> b
    -- ^ /@item@/: The t'GI.Dbusmenu.Objects.Menuitem.Menuitem' to attach the GTK-isms to
    -> c
    -- ^ /@gmi@/: A t'GI.Gtk.Objects.MenuItem.MenuItem' representing the GTK world\'s view of this menuitem
    -> d
    -- ^ /@parent@/: The parent t'GI.Dbusmenu.Objects.Menuitem.Menuitem'
    -> m ()
clientNewitemBase :: a -> b -> c -> d -> m ()
clientNewitemBase client :: a
client item :: b
item gmi :: c
gmi parent :: d
parent = 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 Client
client' <- a -> IO (Ptr Client)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
client
    Ptr Menuitem
item' <- b -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
item
    Ptr MenuItem
gmi' <- c -> IO (Ptr MenuItem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
gmi
    Ptr Menuitem
parent' <- d -> IO (Ptr Menuitem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr d
parent
    Ptr Client -> Ptr Menuitem -> Ptr MenuItem -> Ptr Menuitem -> IO ()
dbusmenu_gtkclient_newitem_base Ptr Client
client' Ptr Menuitem
item' Ptr MenuItem
gmi' Ptr Menuitem
parent'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
client
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
item
    c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr c
gmi
    d -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr d
parent
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ClientNewitemBaseMethodInfo
instance (signature ~ (b -> c -> d -> m ()), MonadIO m, IsClient a, Dbusmenu.Menuitem.IsMenuitem b, Gtk.MenuItem.IsMenuItem c, Dbusmenu.Menuitem.IsMenuitem d) => O.MethodInfo ClientNewitemBaseMethodInfo a signature where
    overloadedMethod = clientNewitemBase

#endif

-- method Client::set_accel_group
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "client"
--           , argType =
--               TInterface Name { namespace = "DbusmenuGtk3" , name = "Client" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "To set the group on"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "agroup"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "AccelGroup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The new acceleration group"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "dbusmenu_gtkclient_set_accel_group" dbusmenu_gtkclient_set_accel_group :: 
    Ptr Client ->                           -- client : TInterface (Name {namespace = "DbusmenuGtk3", name = "Client"})
    Ptr Gtk.AccelGroup.AccelGroup ->        -- agroup : TInterface (Name {namespace = "Gtk", name = "AccelGroup"})
    IO ()

-- | Sets the acceleration group for the menu items with accelerators
-- on this client.
clientSetAccelGroup ::
    (B.CallStack.HasCallStack, MonadIO m, IsClient a, Gtk.AccelGroup.IsAccelGroup b) =>
    a
    -- ^ /@client@/: To set the group on
    -> b
    -- ^ /@agroup@/: The new acceleration group
    -> m ()
clientSetAccelGroup :: a -> b -> m ()
clientSetAccelGroup client :: a
client agroup :: b
agroup = 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 Client
client' <- a -> IO (Ptr Client)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
client
    Ptr AccelGroup
agroup' <- b -> IO (Ptr AccelGroup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
agroup
    Ptr Client -> Ptr AccelGroup -> IO ()
dbusmenu_gtkclient_set_accel_group Ptr Client
client' Ptr AccelGroup
agroup'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
client
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
agroup
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ClientSetAccelGroupMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsClient a, Gtk.AccelGroup.IsAccelGroup b) => O.MethodInfo ClientSetAccelGroupMethodInfo a signature where
    overloadedMethod = clientSetAccelGroup

#endif