{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (inaki@blueleaf.cc)

/No description available in the introspection data./
-}

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

module GI.WebKit2WebExtension.Structs.ContextMenu_
    (

-- * Exported types
    ContextMenu_(..)                        ,
    newZeroContextMenu_                     ,
    noContextMenu_                          ,


 -- * Properties
-- ** parent #attr:parent#
{- | /No description available in the introspection data./
-}
    clearContextMenu_Parent                 ,
#if ENABLE_OVERLOADING
    contextMenu__parent                     ,
#endif
    getContextMenu_Parent                   ,
    setContextMenu_Parent                   ,




    ) 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.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 ContextMenu_ = ContextMenu_ (ManagedPtr ContextMenu_)
instance WrappedPtr ContextMenu_ where
    wrappedPtrCalloc = callocBytes 32
    wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 32 >=> wrapPtr ContextMenu_)
    wrappedPtrFree = Just ptr_to_g_free

-- | Construct a `ContextMenu_` struct initialized to zero.
newZeroContextMenu_ :: MonadIO m => m ContextMenu_
newZeroContextMenu_ = liftIO $ wrappedPtrCalloc >>= wrapPtr ContextMenu_

instance tag ~ 'AttrSet => Constructible ContextMenu_ tag where
    new _ attrs = do
        o <- newZeroContextMenu_
        GI.Attributes.set o attrs
        return o


-- | A convenience alias for `Nothing` :: `Maybe` `ContextMenu_`.
noContextMenu_ :: Maybe ContextMenu_
noContextMenu_ = Nothing

{- |
Get the value of the “@parent@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' contextMenu_ #parent
@
-}
getContextMenu_Parent :: MonadIO m => ContextMenu_ -> m (Maybe GObject.Object.Object)
getContextMenu_Parent s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO (Ptr GObject.Object.Object)
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- (newObject GObject.Object.Object) val'
        return val''
    return result

{- |
Set the value of the “@parent@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' contextMenu_ [ #parent 'Data.GI.Base.Attributes.:=' value ]
@
-}
setContextMenu_Parent :: MonadIO m => ContextMenu_ -> Ptr GObject.Object.Object -> m ()
setContextMenu_Parent s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (val :: Ptr GObject.Object.Object)

{- |
Set the value of the “@parent@” field to `Nothing`.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.clear' #parent
@
-}
clearContextMenu_Parent :: MonadIO m => ContextMenu_ -> m ()
clearContextMenu_Parent s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (FP.nullPtr :: Ptr GObject.Object.Object)

#if ENABLE_OVERLOADING
data ContextMenu_ParentFieldInfo
instance AttrInfo ContextMenu_ParentFieldInfo where
    type AttrAllowedOps ContextMenu_ParentFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ContextMenu_ParentFieldInfo = (~) (Ptr GObject.Object.Object)
    type AttrBaseTypeConstraint ContextMenu_ParentFieldInfo = (~) ContextMenu_
    type AttrGetType ContextMenu_ParentFieldInfo = Maybe GObject.Object.Object
    type AttrLabel ContextMenu_ParentFieldInfo = "parent"
    type AttrOrigin ContextMenu_ParentFieldInfo = ContextMenu_
    attrGet _ = getContextMenu_Parent
    attrSet _ = setContextMenu_Parent
    attrConstruct = undefined
    attrClear _ = clearContextMenu_Parent

contextMenu__parent :: AttrLabelProxy "parent"
contextMenu__parent = AttrLabelProxy

#endif



#if ENABLE_OVERLOADING
instance O.HasAttributeList ContextMenu_
type instance O.AttributeList ContextMenu_ = ContextMenu_AttributeList
type ContextMenu_AttributeList = ('[ '("parent", ContextMenu_ParentFieldInfo)] :: [(Symbol, *)])
#endif

#if ENABLE_OVERLOADING
type family ResolveContextMenu_Method (t :: Symbol) (o :: *) :: * where
    ResolveContextMenu_Method l o = O.MethodResolutionFailed l o

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

#endif