{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A t'GI.Gtk.Structs.TargetPair.TargetPair' is used to represent the same
-- information as a table of t'GI.Gtk.Structs.TargetEntry.TargetEntry', but in
-- an efficient form.

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

module GI.Gtk.Structs.TargetPair
    ( 

-- * Exported types
    TargetPair(..)                          ,
    newZeroTargetPair                       ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveTargetPairMethod                 ,
#endif




 -- * Properties
-- ** flags #attr:flags#
-- | t'GI.Gtk.Flags.TargetFlags' for DND

    getTargetPairFlags                      ,
    setTargetPairFlags                      ,
#if defined(ENABLE_OVERLOADING)
    targetPair_flags                        ,
#endif


-- ** info #attr:info#
-- | an application-assigned integer ID which will
--     get passed as a parameter to e.g the [selectionGet]("GI.Gtk.Objects.Widget#signal:selectionGet")
--     signal. It allows the application to identify the target
--     type without extensive string compares.

    getTargetPairInfo                       ,
    setTargetPairInfo                       ,
#if defined(ENABLE_OVERLOADING)
    targetPair_info                         ,
#endif


-- ** target #attr:target#
-- | t'GI.Gdk.Structs.Atom.Atom' representation of the target type

    getTargetPairTarget                     ,
#if defined(ENABLE_OVERLOADING)
    targetPair_target                       ,
#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.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 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 GI.Gdk.Structs.Atom as Gdk.Atom

-- | Memory-managed wrapper type.
newtype TargetPair = TargetPair (ManagedPtr TargetPair)
    deriving (TargetPair -> TargetPair -> Bool
(TargetPair -> TargetPair -> Bool)
-> (TargetPair -> TargetPair -> Bool) -> Eq TargetPair
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TargetPair -> TargetPair -> Bool
$c/= :: TargetPair -> TargetPair -> Bool
== :: TargetPair -> TargetPair -> Bool
$c== :: TargetPair -> TargetPair -> Bool
Eq)
instance WrappedPtr TargetPair where
    wrappedPtrCalloc :: IO (Ptr TargetPair)
wrappedPtrCalloc = Int -> IO (Ptr TargetPair)
forall a. Int -> IO (Ptr a)
callocBytes Int
16
    wrappedPtrCopy :: TargetPair -> IO TargetPair
wrappedPtrCopy = \TargetPair
p -> TargetPair -> (Ptr TargetPair -> IO TargetPair) -> IO TargetPair
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TargetPair
p (Int -> Ptr TargetPair -> IO (Ptr TargetPair)
forall a. WrappedPtr a => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
16 (Ptr TargetPair -> IO (Ptr TargetPair))
-> (Ptr TargetPair -> IO TargetPair)
-> Ptr TargetPair
-> IO TargetPair
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr TargetPair -> TargetPair)
-> Ptr TargetPair -> IO TargetPair
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr TargetPair -> TargetPair
TargetPair)
    wrappedPtrFree :: Maybe (GDestroyNotify TargetPair)
wrappedPtrFree = GDestroyNotify TargetPair -> Maybe (GDestroyNotify TargetPair)
forall a. a -> Maybe a
Just GDestroyNotify TargetPair
forall a. FunPtr (Ptr a -> IO ())
ptr_to_g_free

-- | Construct a `TargetPair` struct initialized to zero.
newZeroTargetPair :: MonadIO m => m TargetPair
newZeroTargetPair :: m TargetPair
newZeroTargetPair = IO TargetPair -> m TargetPair
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TargetPair -> m TargetPair) -> IO TargetPair -> m TargetPair
forall a b. (a -> b) -> a -> b
$ IO (Ptr TargetPair)
forall a. WrappedPtr a => IO (Ptr a)
wrappedPtrCalloc IO (Ptr TargetPair)
-> (Ptr TargetPair -> IO TargetPair) -> IO TargetPair
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr TargetPair -> TargetPair)
-> Ptr TargetPair -> IO TargetPair
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr TargetPair -> TargetPair
TargetPair

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


-- | Get the value of the “@target@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' targetPair #target
-- @
getTargetPairTarget :: MonadIO m => TargetPair -> m Gdk.Atom.Atom
getTargetPairTarget :: TargetPair -> m Atom
getTargetPairTarget TargetPair
s = IO Atom -> m Atom
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Atom -> m Atom) -> IO Atom -> m Atom
forall a b. (a -> b) -> a -> b
$ TargetPair -> (Ptr TargetPair -> IO Atom) -> IO Atom
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TargetPair
s ((Ptr TargetPair -> IO Atom) -> IO Atom)
-> (Ptr TargetPair -> IO Atom) -> IO Atom
forall a b. (a -> b) -> a -> b
$ \Ptr TargetPair
ptr -> do
    let val :: Ptr Atom
val = Ptr TargetPair
ptr Ptr TargetPair -> Int -> Ptr Atom
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: (Ptr Gdk.Atom.Atom)
    Atom
val' <- ((ManagedPtr Atom -> Atom) -> Ptr Atom -> IO Atom
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr Atom -> Atom
Gdk.Atom.Atom) Ptr Atom
val
    Atom -> IO Atom
forall (m :: * -> *) a. Monad m => a -> m a
return Atom
val'

#if defined(ENABLE_OVERLOADING)
data TargetPairTargetFieldInfo
instance AttrInfo TargetPairTargetFieldInfo where
    type AttrBaseTypeConstraint TargetPairTargetFieldInfo = (~) TargetPair
    type AttrAllowedOps TargetPairTargetFieldInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint TargetPairTargetFieldInfo = (~) (Ptr Gdk.Atom.Atom)
    type AttrTransferTypeConstraint TargetPairTargetFieldInfo = (~)(Ptr Gdk.Atom.Atom)
    type AttrTransferType TargetPairTargetFieldInfo = (Ptr Gdk.Atom.Atom)
    type AttrGetType TargetPairTargetFieldInfo = Gdk.Atom.Atom
    type AttrLabel TargetPairTargetFieldInfo = "target"
    type AttrOrigin TargetPairTargetFieldInfo = TargetPair
    attrGet = getTargetPairTarget
    attrSet = undefined
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer = undefined

targetPair_target :: AttrLabelProxy "target"
targetPair_target = AttrLabelProxy

#endif


-- | Get the value of the “@flags@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' targetPair #flags
-- @
getTargetPairFlags :: MonadIO m => TargetPair -> m Word32
getTargetPairFlags :: TargetPair -> m Word32
getTargetPairFlags TargetPair
s = 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
$ TargetPair -> (Ptr TargetPair -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TargetPair
s ((Ptr TargetPair -> IO Word32) -> IO Word32)
-> (Ptr TargetPair -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \Ptr TargetPair
ptr -> do
    Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr TargetPair
ptr Ptr TargetPair -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) :: IO Word32
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val

-- | Set the value of the “@flags@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' targetPair [ #flags 'Data.GI.Base.Attributes.:=' value ]
-- @
setTargetPairFlags :: MonadIO m => TargetPair -> Word32 -> m ()
setTargetPairFlags :: TargetPair -> Word32 -> m ()
setTargetPairFlags TargetPair
s Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TargetPair -> (Ptr TargetPair -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TargetPair
s ((Ptr TargetPair -> IO ()) -> IO ())
-> (Ptr TargetPair -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TargetPair
ptr -> do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TargetPair
ptr Ptr TargetPair -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (Word32
val :: Word32)

#if defined(ENABLE_OVERLOADING)
data TargetPairFlagsFieldInfo
instance AttrInfo TargetPairFlagsFieldInfo where
    type AttrBaseTypeConstraint TargetPairFlagsFieldInfo = (~) TargetPair
    type AttrAllowedOps TargetPairFlagsFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TargetPairFlagsFieldInfo = (~) Word32
    type AttrTransferTypeConstraint TargetPairFlagsFieldInfo = (~)Word32
    type AttrTransferType TargetPairFlagsFieldInfo = Word32
    type AttrGetType TargetPairFlagsFieldInfo = Word32
    type AttrLabel TargetPairFlagsFieldInfo = "flags"
    type AttrOrigin TargetPairFlagsFieldInfo = TargetPair
    attrGet = getTargetPairFlags
    attrSet = setTargetPairFlags
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

targetPair_flags :: AttrLabelProxy "flags"
targetPair_flags = AttrLabelProxy

#endif


-- | Get the value of the “@info@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' targetPair #info
-- @
getTargetPairInfo :: MonadIO m => TargetPair -> m Word32
getTargetPairInfo :: TargetPair -> m Word32
getTargetPairInfo TargetPair
s = 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
$ TargetPair -> (Ptr TargetPair -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TargetPair
s ((Ptr TargetPair -> IO Word32) -> IO Word32)
-> (Ptr TargetPair -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \Ptr TargetPair
ptr -> do
    Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr TargetPair
ptr Ptr TargetPair -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12) :: IO Word32
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val

-- | Set the value of the “@info@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' targetPair [ #info 'Data.GI.Base.Attributes.:=' value ]
-- @
setTargetPairInfo :: MonadIO m => TargetPair -> Word32 -> m ()
setTargetPairInfo :: TargetPair -> Word32 -> m ()
setTargetPairInfo TargetPair
s Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TargetPair -> (Ptr TargetPair -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TargetPair
s ((Ptr TargetPair -> IO ()) -> IO ())
-> (Ptr TargetPair -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TargetPair
ptr -> do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TargetPair
ptr Ptr TargetPair -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12) (Word32
val :: Word32)

#if defined(ENABLE_OVERLOADING)
data TargetPairInfoFieldInfo
instance AttrInfo TargetPairInfoFieldInfo where
    type AttrBaseTypeConstraint TargetPairInfoFieldInfo = (~) TargetPair
    type AttrAllowedOps TargetPairInfoFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TargetPairInfoFieldInfo = (~) Word32
    type AttrTransferTypeConstraint TargetPairInfoFieldInfo = (~)Word32
    type AttrTransferType TargetPairInfoFieldInfo = Word32
    type AttrGetType TargetPairInfoFieldInfo = Word32
    type AttrLabel TargetPairInfoFieldInfo = "info"
    type AttrOrigin TargetPairInfoFieldInfo = TargetPair
    attrGet = getTargetPairInfo
    attrSet = setTargetPairInfo
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

targetPair_info :: AttrLabelProxy "info"
targetPair_info = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList TargetPair
type instance O.AttributeList TargetPair = TargetPairAttributeList
type TargetPairAttributeList = ('[ '("target", TargetPairTargetFieldInfo), '("flags", TargetPairFlagsFieldInfo), '("info", TargetPairInfoFieldInfo)] :: [(Symbol, *)])
#endif

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

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

#endif