{-# 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.BindingArg.BindingArg' holds the data associated with
-- an argument for a key binding signal emission as
-- stored in t'GI.Gtk.Structs.BindingSignal.BindingSignal'.

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

module GI.Gtk.Structs.BindingArg
    ( 

-- * Exported types
    BindingArg(..)                          ,
    newZeroBindingArg                       ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveBindingArgMethod                 ,
#endif




 -- * Properties
-- ** argType #attr:argType#
-- | implementation detail

#if defined(ENABLE_OVERLOADING)
    bindingArg_argType                      ,
#endif
    getBindingArgArgType                    ,
    setBindingArgArgType                    ,




    ) 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


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

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

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


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

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


-- | Get the value of the “@arg_type@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' bindingArg #argType
-- @
getBindingArgArgType :: MonadIO m => BindingArg -> m GType
getBindingArgArgType :: BindingArg -> m GType
getBindingArgArgType BindingArg
s = IO GType -> m GType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GType -> m GType) -> IO GType -> m GType
forall a b. (a -> b) -> a -> b
$ BindingArg -> (Ptr BindingArg -> IO GType) -> IO GType
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr BindingArg
s ((Ptr BindingArg -> IO GType) -> IO GType)
-> (Ptr BindingArg -> IO GType) -> IO GType
forall a b. (a -> b) -> a -> b
$ \Ptr BindingArg
ptr -> do
    CGType
val <- Ptr CGType -> IO CGType
forall a. Storable a => Ptr a -> IO a
peek (Ptr BindingArg
ptr Ptr BindingArg -> Int -> Ptr CGType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO CGType
    let val' :: GType
val' = CGType -> GType
GType CGType
val
    GType -> IO GType
forall (m :: * -> *) a. Monad m => a -> m a
return GType
val'

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

#if defined(ENABLE_OVERLOADING)
data BindingArgArgTypeFieldInfo
instance AttrInfo BindingArgArgTypeFieldInfo where
    type AttrBaseTypeConstraint BindingArgArgTypeFieldInfo = (~) BindingArg
    type AttrAllowedOps BindingArgArgTypeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint BindingArgArgTypeFieldInfo = (~) GType
    type AttrTransferTypeConstraint BindingArgArgTypeFieldInfo = (~)GType
    type AttrTransferType BindingArgArgTypeFieldInfo = GType
    type AttrGetType BindingArgArgTypeFieldInfo = GType
    type AttrLabel BindingArgArgTypeFieldInfo = "arg_type"
    type AttrOrigin BindingArgArgTypeFieldInfo = BindingArg
    attrGet = getBindingArgArgType
    attrSet = setBindingArgArgType
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

bindingArg_argType :: AttrLabelProxy "argType"
bindingArg_argType = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList BindingArg
type instance O.AttributeList BindingArg = BindingArgAttributeList
type BindingArgAttributeList = ('[ '("argType", BindingArgArgTypeFieldInfo)] :: [(Symbol, *)])
#endif

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

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

#endif