{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Public instance data for a t'GI.Dbusmenu.Objects.MenuitemProxy.MenuitemProxy'.

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

module GI.Dbusmenu.Objects.MenuitemProxy
    ( 

-- * Exported types
    MenuitemProxy(..)                       ,
    IsMenuitemProxy                         ,
    toMenuitemProxy                         ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [childAddPosition]("GI.Dbusmenu.Objects.Menuitem#g:method:childAddPosition"), [childAppend]("GI.Dbusmenu.Objects.Menuitem#g:method:childAppend"), [childDelete]("GI.Dbusmenu.Objects.Menuitem#g:method:childDelete"), [childFind]("GI.Dbusmenu.Objects.Menuitem#g:method:childFind"), [childPrepend]("GI.Dbusmenu.Objects.Menuitem#g:method:childPrepend"), [childReorder]("GI.Dbusmenu.Objects.Menuitem#g:method:childReorder"), [findId]("GI.Dbusmenu.Objects.Menuitem#g:method:findId"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [foreach]("GI.Dbusmenu.Objects.Menuitem#g:method:foreach"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [handleEvent]("GI.Dbusmenu.Objects.Menuitem#g:method:handleEvent"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [propertiesCopy]("GI.Dbusmenu.Objects.Menuitem#g:method:propertiesCopy"), [propertiesList]("GI.Dbusmenu.Objects.Menuitem#g:method:propertiesList"), [propertyExist]("GI.Dbusmenu.Objects.Menuitem#g:method:propertyExist"), [propertyGet]("GI.Dbusmenu.Objects.Menuitem#g:method:propertyGet"), [propertyGetBool]("GI.Dbusmenu.Objects.Menuitem#g:method:propertyGetBool"), [propertyGetByteArray]("GI.Dbusmenu.Objects.Menuitem#g:method:propertyGetByteArray"), [propertyGetInt]("GI.Dbusmenu.Objects.Menuitem#g:method:propertyGetInt"), [propertyGetVariant]("GI.Dbusmenu.Objects.Menuitem#g:method:propertyGetVariant"), [propertyRemove]("GI.Dbusmenu.Objects.Menuitem#g:method:propertyRemove"), [propertySet]("GI.Dbusmenu.Objects.Menuitem#g:method:propertySet"), [propertySetBool]("GI.Dbusmenu.Objects.Menuitem#g:method:propertySetBool"), [propertySetByteArray]("GI.Dbusmenu.Objects.Menuitem#g:method:propertySetByteArray"), [propertySetInt]("GI.Dbusmenu.Objects.Menuitem#g:method:propertySetInt"), [propertySetVariant]("GI.Dbusmenu.Objects.Menuitem#g:method:propertySetVariant"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [sendAboutToShow]("GI.Dbusmenu.Objects.Menuitem#g:method:sendAboutToShow"), [showToUser]("GI.Dbusmenu.Objects.Menuitem#g:method:showToUser"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [takeChildren]("GI.Dbusmenu.Objects.Menuitem#g:method:takeChildren"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unparent]("GI.Dbusmenu.Objects.Menuitem#g:method:unparent"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getChildren]("GI.Dbusmenu.Objects.Menuitem#g:method:getChildren"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getId]("GI.Dbusmenu.Objects.Menuitem#g:method:getId"), [getParent]("GI.Dbusmenu.Objects.Menuitem#g:method:getParent"), [getPosition]("GI.Dbusmenu.Objects.Menuitem#g:method:getPosition"), [getPositionRealized]("GI.Dbusmenu.Objects.Menuitem#g:method:getPositionRealized"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRoot]("GI.Dbusmenu.Objects.Menuitem#g:method:getRoot"), [getWrapped]("GI.Dbusmenu.Objects.MenuitemProxy#g:method:getWrapped").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setParent]("GI.Dbusmenu.Objects.Menuitem#g:method:setParent"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setRoot]("GI.Dbusmenu.Objects.Menuitem#g:method:setRoot").

#if defined(ENABLE_OVERLOADING)
    ResolveMenuitemProxyMethod              ,
#endif

-- ** getWrapped #method:getWrapped#

#if defined(ENABLE_OVERLOADING)
    MenuitemProxyGetWrappedMethodInfo       ,
#endif
    menuitemProxyGetWrapped                 ,


-- ** new #method:new#

    menuitemProxyNew                        ,




 -- * Properties


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

#if defined(ENABLE_OVERLOADING)
    MenuitemProxyMenuItemPropertyInfo       ,
#endif
    constructMenuitemProxyMenuItem          ,
    getMenuitemProxyMenuItem                ,
#if defined(ENABLE_OVERLOADING)
    menuitemProxyMenuItem                   ,
#endif




    ) where

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

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

import {-# SOURCE #-} qualified GI.Dbusmenu.Objects.Menuitem as Dbusmenu.Menuitem
import qualified GI.GObject.Objects.Object as GObject.Object

-- | Memory-managed wrapper type.
newtype MenuitemProxy = MenuitemProxy (SP.ManagedPtr MenuitemProxy)
    deriving (MenuitemProxy -> MenuitemProxy -> Bool
(MenuitemProxy -> MenuitemProxy -> Bool)
-> (MenuitemProxy -> MenuitemProxy -> Bool) -> Eq MenuitemProxy
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MenuitemProxy -> MenuitemProxy -> Bool
== :: MenuitemProxy -> MenuitemProxy -> Bool
$c/= :: MenuitemProxy -> MenuitemProxy -> Bool
/= :: MenuitemProxy -> MenuitemProxy -> Bool
Eq)

instance SP.ManagedPtrNewtype MenuitemProxy where
    toManagedPtr :: MenuitemProxy -> ManagedPtr MenuitemProxy
toManagedPtr (MenuitemProxy ManagedPtr MenuitemProxy
p) = ManagedPtr MenuitemProxy
p

foreign import ccall "dbusmenu_menuitem_proxy_get_type"
    c_dbusmenu_menuitem_proxy_get_type :: IO B.Types.GType

instance B.Types.TypedObject MenuitemProxy where
    glibType :: IO GType
glibType = IO GType
c_dbusmenu_menuitem_proxy_get_type

instance B.Types.GObject MenuitemProxy

-- | Type class for types which can be safely cast to `MenuitemProxy`, for instance with `toMenuitemProxy`.
class (SP.GObject o, O.IsDescendantOf MenuitemProxy o) => IsMenuitemProxy o
instance (SP.GObject o, O.IsDescendantOf MenuitemProxy o) => IsMenuitemProxy o

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

-- | Cast to `MenuitemProxy`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toMenuitemProxy :: (MIO.MonadIO m, IsMenuitemProxy o) => o -> m MenuitemProxy
toMenuitemProxy :: forall (m :: * -> *) o.
(MonadIO m, IsMenuitemProxy o) =>
o -> m MenuitemProxy
toMenuitemProxy = IO MenuitemProxy -> m MenuitemProxy
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO MenuitemProxy -> m MenuitemProxy)
-> (o -> IO MenuitemProxy) -> o -> m MenuitemProxy
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr MenuitemProxy -> MenuitemProxy)
-> o -> IO MenuitemProxy
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr MenuitemProxy -> MenuitemProxy
MenuitemProxy

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

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

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

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

#endif

instance (info ~ ResolveMenuitemProxyMethod t MenuitemProxy, O.OverloadedMethodInfo info MenuitemProxy) => OL.IsLabel t (O.MethodProxy info MenuitemProxy) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

-- VVV Prop "menu-item"
   -- Type: TInterface (Name {namespace = "Dbusmenu", name = "Menuitem"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@menu-item@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' menuitemProxy #menuItem
-- @
getMenuitemProxyMenuItem :: (MonadIO m, IsMenuitemProxy o) => o -> m (Maybe Dbusmenu.Menuitem.Menuitem)
getMenuitemProxyMenuItem :: forall (m :: * -> *) o.
(MonadIO m, IsMenuitemProxy o) =>
o -> m (Maybe Menuitem)
getMenuitemProxyMenuItem o
obj = IO (Maybe Menuitem) -> m (Maybe Menuitem)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Menuitem) -> m (Maybe Menuitem))
-> IO (Maybe Menuitem) -> m (Maybe Menuitem)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr Menuitem -> Menuitem)
-> IO (Maybe Menuitem)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"menu-item" ManagedPtr Menuitem -> Menuitem
Dbusmenu.Menuitem.Menuitem

-- | Construct a `GValueConstruct` with valid value for the “@menu-item@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructMenuitemProxyMenuItem :: (IsMenuitemProxy o, MIO.MonadIO m, Dbusmenu.Menuitem.IsMenuitem a) => a -> m (GValueConstruct o)
constructMenuitemProxyMenuItem :: forall o (m :: * -> *) a.
(IsMenuitemProxy o, MonadIO m, IsMenuitem a) =>
a -> m (GValueConstruct o)
constructMenuitemProxyMenuItem a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"menu-item" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

#if defined(ENABLE_OVERLOADING)
data MenuitemProxyMenuItemPropertyInfo
instance AttrInfo MenuitemProxyMenuItemPropertyInfo where
    type AttrAllowedOps MenuitemProxyMenuItemPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint MenuitemProxyMenuItemPropertyInfo = IsMenuitemProxy
    type AttrSetTypeConstraint MenuitemProxyMenuItemPropertyInfo = Dbusmenu.Menuitem.IsMenuitem
    type AttrTransferTypeConstraint MenuitemProxyMenuItemPropertyInfo = Dbusmenu.Menuitem.IsMenuitem
    type AttrTransferType MenuitemProxyMenuItemPropertyInfo = Dbusmenu.Menuitem.Menuitem
    type AttrGetType MenuitemProxyMenuItemPropertyInfo = (Maybe Dbusmenu.Menuitem.Menuitem)
    type AttrLabel MenuitemProxyMenuItemPropertyInfo = "menu-item"
    type AttrOrigin MenuitemProxyMenuItemPropertyInfo = MenuitemProxy
    attrGet = getMenuitemProxyMenuItem
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Dbusmenu.Menuitem.Menuitem v
    attrConstruct = constructMenuitemProxyMenuItem
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Dbusmenu.Objects.MenuitemProxy.menuItem"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dbusmenu-0.4.11/docs/GI-Dbusmenu-Objects-MenuitemProxy.html#g:attr:menuItem"
        })
#endif

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

#if defined(ENABLE_OVERLOADING)
menuitemProxyMenuItem :: AttrLabelProxy "menuItem"
menuitemProxyMenuItem = AttrLabelProxy

#endif

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

#endif

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

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

-- | Builds a new t'GI.Dbusmenu.Objects.MenuitemProxy.MenuitemProxy' object that proxies
-- all of the values for /@mi@/.
menuitemProxyNew ::
    (B.CallStack.HasCallStack, MonadIO m, Dbusmenu.Menuitem.IsMenuitem a) =>
    a
    -- ^ /@mi@/: The t'GI.Dbusmenu.Objects.Menuitem.Menuitem' to proxy
    -> m MenuitemProxy
    -- ^ __Returns:__ A new t'GI.Dbusmenu.Objects.MenuitemProxy.MenuitemProxy' object.
menuitemProxyNew :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMenuitem a) =>
a -> m MenuitemProxy
menuitemProxyNew a
mi = IO MenuitemProxy -> m MenuitemProxy
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO MenuitemProxy -> m MenuitemProxy)
-> IO MenuitemProxy -> m MenuitemProxy
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 MenuitemProxy
result <- Ptr Menuitem -> IO (Ptr MenuitemProxy)
dbusmenu_menuitem_proxy_new Ptr Menuitem
mi'
    Text -> Ptr MenuitemProxy -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"menuitemProxyNew" Ptr MenuitemProxy
result
    MenuitemProxy
result' <- ((ManagedPtr MenuitemProxy -> MenuitemProxy)
-> Ptr MenuitemProxy -> IO MenuitemProxy
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr MenuitemProxy -> MenuitemProxy
MenuitemProxy) Ptr MenuitemProxy
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mi
    MenuitemProxy -> IO MenuitemProxy
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return MenuitemProxy
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method MenuitemProxy::get_wrapped
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pmi"
--           , argType =
--               TInterface Name { namespace = "Dbusmenu" , name = "MenuitemProxy" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "#DbusmenuMenuitemProxy to look into"
--                 , 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_proxy_get_wrapped" dbusmenu_menuitem_proxy_get_wrapped :: 
    Ptr MenuitemProxy ->                    -- pmi : TInterface (Name {namespace = "Dbusmenu", name = "MenuitemProxy"})
    IO (Ptr Dbusmenu.Menuitem.Menuitem)

-- | Accesses the private variable of which t'GI.Dbusmenu.Objects.Menuitem.Menuitem'
-- we are doing the proxying for.
menuitemProxyGetWrapped ::
    (B.CallStack.HasCallStack, MonadIO m, IsMenuitemProxy a) =>
    a
    -- ^ /@pmi@/: t'GI.Dbusmenu.Objects.MenuitemProxy.MenuitemProxy' to look into
    -> m Dbusmenu.Menuitem.Menuitem
    -- ^ __Returns:__ A t'GI.Dbusmenu.Objects.Menuitem.Menuitem' object or a @/NULL/@ if we
    -- 	don\'t have one or there is an error.
menuitemProxyGetWrapped :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMenuitemProxy a) =>
a -> m Menuitem
menuitemProxyGetWrapped a
pmi = IO Menuitem -> m Menuitem
forall a. IO a -> m a
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 MenuitemProxy
pmi' <- a -> IO (Ptr MenuitemProxy)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pmi
    Ptr Menuitem
result <- Ptr MenuitemProxy -> IO (Ptr Menuitem)
dbusmenu_menuitem_proxy_get_wrapped Ptr MenuitemProxy
pmi'
    Text -> Ptr Menuitem -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"menuitemProxyGetWrapped" 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
Dbusmenu.Menuitem.Menuitem) Ptr Menuitem
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pmi
    Menuitem -> IO Menuitem
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Menuitem
result'

#if defined(ENABLE_OVERLOADING)
data MenuitemProxyGetWrappedMethodInfo
instance (signature ~ (m Dbusmenu.Menuitem.Menuitem), MonadIO m, IsMenuitemProxy a) => O.OverloadedMethod MenuitemProxyGetWrappedMethodInfo a signature where
    overloadedMethod = menuitemProxyGetWrapped

instance O.OverloadedMethodInfo MenuitemProxyGetWrappedMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Dbusmenu.Objects.MenuitemProxy.menuitemProxyGetWrapped",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dbusmenu-0.4.11/docs/GI-Dbusmenu-Objects-MenuitemProxy.html#v:menuitemProxyGetWrapped"
        })


#endif