{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

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

module GI.WebKit2WebExtension.Structs.ContextMenuItem_
    ( 

-- * Exported types
    ContextMenuItem_(..)                    ,
    newZeroContextMenuItem_                 ,


 -- * Methods

#if defined(ENABLE_OVERLOADING)
    ResolveContextMenuItem_Method           ,
#endif



 -- * Properties


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

    clearContextMenuItem_Parent             ,
#if defined(ENABLE_OVERLOADING)
    contextMenuItem__parent                 ,
#endif
    getContextMenuItem_Parent               ,
    setContextMenuItem_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.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

import qualified GI.GObject.Objects.InitiallyUnowned as GObject.InitiallyUnowned

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

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

instance BoxedPtr ContextMenuItem_ where
    boxedPtrCopy :: ContextMenuItem_ -> IO ContextMenuItem_
boxedPtrCopy = \ContextMenuItem_
p -> ContextMenuItem_
-> (Ptr ContextMenuItem_ -> IO ContextMenuItem_)
-> IO ContextMenuItem_
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr ContextMenuItem_
p (Int -> Ptr ContextMenuItem_ -> IO (Ptr ContextMenuItem_)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
32 (Ptr ContextMenuItem_ -> IO (Ptr ContextMenuItem_))
-> (Ptr ContextMenuItem_ -> IO ContextMenuItem_)
-> Ptr ContextMenuItem_
-> IO ContextMenuItem_
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr ContextMenuItem_ -> ContextMenuItem_)
-> Ptr ContextMenuItem_ -> IO ContextMenuItem_
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr ContextMenuItem_ -> ContextMenuItem_
ContextMenuItem_)
    boxedPtrFree :: ContextMenuItem_ -> IO ()
boxedPtrFree = \ContextMenuItem_
x -> ContextMenuItem_ -> (Ptr ContextMenuItem_ -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr ContextMenuItem_
x Ptr ContextMenuItem_ -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr ContextMenuItem_ where
    boxedPtrCalloc :: IO (Ptr ContextMenuItem_)
boxedPtrCalloc = Int -> IO (Ptr ContextMenuItem_)
forall a. Int -> IO (Ptr a)
callocBytes Int
32


-- | Construct a `ContextMenuItem_` struct initialized to zero.
newZeroContextMenuItem_ :: MonadIO m => m ContextMenuItem_
newZeroContextMenuItem_ :: forall (m :: * -> *). MonadIO m => m ContextMenuItem_
newZeroContextMenuItem_ = IO ContextMenuItem_ -> m ContextMenuItem_
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ContextMenuItem_ -> m ContextMenuItem_)
-> IO ContextMenuItem_ -> m ContextMenuItem_
forall a b. (a -> b) -> a -> b
$ IO (Ptr ContextMenuItem_)
forall a. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr ContextMenuItem_)
-> (Ptr ContextMenuItem_ -> IO ContextMenuItem_)
-> IO ContextMenuItem_
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr ContextMenuItem_ -> ContextMenuItem_)
-> Ptr ContextMenuItem_ -> IO ContextMenuItem_
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr ContextMenuItem_ -> ContextMenuItem_
ContextMenuItem_

instance tag ~ 'AttrSet => Constructible ContextMenuItem_ tag where
    new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr ContextMenuItem_ -> ContextMenuItem_)
-> [AttrOp ContextMenuItem_ tag] -> m ContextMenuItem_
new ManagedPtr ContextMenuItem_ -> ContextMenuItem_
_ [AttrOp ContextMenuItem_ tag]
attrs = do
        ContextMenuItem_
o <- m ContextMenuItem_
forall (m :: * -> *). MonadIO m => m ContextMenuItem_
newZeroContextMenuItem_
        ContextMenuItem_ -> [AttrOp ContextMenuItem_ 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set ContextMenuItem_
o [AttrOp ContextMenuItem_ tag]
[AttrOp ContextMenuItem_ 'AttrSet]
attrs
        ContextMenuItem_ -> m ContextMenuItem_
forall (m :: * -> *) a. Monad m => a -> m a
return ContextMenuItem_
o


-- | 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' contextMenuItem_ #parent
-- @
getContextMenuItem_Parent :: MonadIO m => ContextMenuItem_ -> m (Maybe GObject.InitiallyUnowned.InitiallyUnowned)
getContextMenuItem_Parent :: forall (m :: * -> *).
MonadIO m =>
ContextMenuItem_ -> m (Maybe InitiallyUnowned)
getContextMenuItem_Parent ContextMenuItem_
s = IO (Maybe InitiallyUnowned) -> m (Maybe InitiallyUnowned)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe InitiallyUnowned) -> m (Maybe InitiallyUnowned))
-> IO (Maybe InitiallyUnowned) -> m (Maybe InitiallyUnowned)
forall a b. (a -> b) -> a -> b
$ ContextMenuItem_
-> (Ptr ContextMenuItem_ -> IO (Maybe InitiallyUnowned))
-> IO (Maybe InitiallyUnowned)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ContextMenuItem_
s ((Ptr ContextMenuItem_ -> IO (Maybe InitiallyUnowned))
 -> IO (Maybe InitiallyUnowned))
-> (Ptr ContextMenuItem_ -> IO (Maybe InitiallyUnowned))
-> IO (Maybe InitiallyUnowned)
forall a b. (a -> b) -> a -> b
$ \Ptr ContextMenuItem_
ptr -> do
    Ptr InitiallyUnowned
val <- Ptr (Ptr InitiallyUnowned) -> IO (Ptr InitiallyUnowned)
forall a. Storable a => Ptr a -> IO a
peek (Ptr ContextMenuItem_
ptr Ptr ContextMenuItem_ -> Int -> Ptr (Ptr InitiallyUnowned)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO (Ptr GObject.InitiallyUnowned.InitiallyUnowned)
    Maybe InitiallyUnowned
result <- Ptr InitiallyUnowned
-> (Ptr InitiallyUnowned -> IO InitiallyUnowned)
-> IO (Maybe InitiallyUnowned)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr InitiallyUnowned
val ((Ptr InitiallyUnowned -> IO InitiallyUnowned)
 -> IO (Maybe InitiallyUnowned))
-> (Ptr InitiallyUnowned -> IO InitiallyUnowned)
-> IO (Maybe InitiallyUnowned)
forall a b. (a -> b) -> a -> b
$ \Ptr InitiallyUnowned
val' -> do
        InitiallyUnowned
val'' <- ((ManagedPtr InitiallyUnowned -> InitiallyUnowned)
-> Ptr InitiallyUnowned -> IO InitiallyUnowned
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr InitiallyUnowned -> InitiallyUnowned
GObject.InitiallyUnowned.InitiallyUnowned) Ptr InitiallyUnowned
val'
        InitiallyUnowned -> IO InitiallyUnowned
forall (m :: * -> *) a. Monad m => a -> m a
return InitiallyUnowned
val''
    Maybe InitiallyUnowned -> IO (Maybe InitiallyUnowned)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe InitiallyUnowned
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' contextMenuItem_ [ #parent 'Data.GI.Base.Attributes.:=' value ]
-- @
setContextMenuItem_Parent :: MonadIO m => ContextMenuItem_ -> Ptr GObject.InitiallyUnowned.InitiallyUnowned -> m ()
setContextMenuItem_Parent :: forall (m :: * -> *).
MonadIO m =>
ContextMenuItem_ -> Ptr InitiallyUnowned -> m ()
setContextMenuItem_Parent ContextMenuItem_
s Ptr InitiallyUnowned
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ ContextMenuItem_ -> (Ptr ContextMenuItem_ -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ContextMenuItem_
s ((Ptr ContextMenuItem_ -> IO ()) -> IO ())
-> (Ptr ContextMenuItem_ -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr ContextMenuItem_
ptr -> do
    Ptr (Ptr InitiallyUnowned) -> Ptr InitiallyUnowned -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ContextMenuItem_
ptr Ptr ContextMenuItem_ -> Int -> Ptr (Ptr InitiallyUnowned)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (Ptr InitiallyUnowned
val :: Ptr GObject.InitiallyUnowned.InitiallyUnowned)

-- | 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
-- @
clearContextMenuItem_Parent :: MonadIO m => ContextMenuItem_ -> m ()
clearContextMenuItem_Parent :: forall (m :: * -> *). MonadIO m => ContextMenuItem_ -> m ()
clearContextMenuItem_Parent ContextMenuItem_
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ ContextMenuItem_ -> (Ptr ContextMenuItem_ -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ContextMenuItem_
s ((Ptr ContextMenuItem_ -> IO ()) -> IO ())
-> (Ptr ContextMenuItem_ -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr ContextMenuItem_
ptr -> do
    Ptr (Ptr InitiallyUnowned) -> Ptr InitiallyUnowned -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ContextMenuItem_
ptr Ptr ContextMenuItem_ -> Int -> Ptr (Ptr InitiallyUnowned)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (Ptr InitiallyUnowned
forall a. Ptr a
FP.nullPtr :: Ptr GObject.InitiallyUnowned.InitiallyUnowned)

#if defined(ENABLE_OVERLOADING)
data ContextMenuItem_ParentFieldInfo
instance AttrInfo ContextMenuItem_ParentFieldInfo where
    type AttrBaseTypeConstraint ContextMenuItem_ParentFieldInfo = (~) ContextMenuItem_
    type AttrAllowedOps ContextMenuItem_ParentFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ContextMenuItem_ParentFieldInfo = (~) (Ptr GObject.InitiallyUnowned.InitiallyUnowned)
    type AttrTransferTypeConstraint ContextMenuItem_ParentFieldInfo = (~)(Ptr GObject.InitiallyUnowned.InitiallyUnowned)
    type AttrTransferType ContextMenuItem_ParentFieldInfo = (Ptr GObject.InitiallyUnowned.InitiallyUnowned)
    type AttrGetType ContextMenuItem_ParentFieldInfo = Maybe GObject.InitiallyUnowned.InitiallyUnowned
    type AttrLabel ContextMenuItem_ParentFieldInfo = "parent"
    type AttrOrigin ContextMenuItem_ParentFieldInfo = ContextMenuItem_
    attrGet = getContextMenuItem_Parent
    attrSet = setContextMenuItem_Parent
    attrConstruct = undefined
    attrClear = clearContextMenuItem_Parent
    attrTransfer _ v = do
        return v

contextMenuItem__parent :: AttrLabelProxy "parent"
contextMenuItem__parent = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ContextMenuItem_
type instance O.AttributeList ContextMenuItem_ = ContextMenuItem_AttributeList
type ContextMenuItem_AttributeList = ('[ '("parent", ContextMenuItem_ParentFieldInfo)] :: [(Symbol, *)])
#endif

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

instance (info ~ ResolveContextMenuItem_Method t ContextMenuItem_, O.OverloadedMethod info ContextMenuItem_ p) => OL.IsLabel t (ContextMenuItem_ -> 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 ~ ResolveContextMenuItem_Method t ContextMenuItem_, O.OverloadedMethod info ContextMenuItem_ p, R.HasField t ContextMenuItem_ p) => R.HasField t ContextMenuItem_ p where
    getField = O.overloadedMethod @info

#endif

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

#endif