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

VTable for the 'GI.GObject.Structs.Value.Value' /@type@/.
-}

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

module GI.Gst.Structs.ValueTable
    (

-- * Exported types
    ValueTable(..)                          ,
    newZeroValueTable                       ,
    noValueTable                            ,


 -- * Properties
-- ** compare #attr:compare#
{- | a 'GI.Gst.Callbacks.ValueCompareFunc'
-}
    clearValueTableCompare                  ,
    getValueTableCompare                    ,
    setValueTableCompare                    ,
#if ENABLE_OVERLOADING
    valueTable_compare                      ,
#endif


-- ** deserialize #attr:deserialize#
{- | a 'GI.Gst.Callbacks.ValueDeserializeFunc'
-}
    clearValueTableDeserialize              ,
    getValueTableDeserialize                ,
    setValueTableDeserialize                ,
#if ENABLE_OVERLOADING
    valueTable_deserialize                  ,
#endif


-- ** serialize #attr:serialize#
{- | a 'GI.Gst.Callbacks.ValueSerializeFunc'
-}
    clearValueTableSerialize                ,
    getValueTableSerialize                  ,
    setValueTableSerialize                  ,
#if ENABLE_OVERLOADING
    valueTable_serialize                    ,
#endif


-- ** type #attr:type#
{- | a 'GType'
-}
    getValueTableType                       ,
    setValueTableType                       ,
#if ENABLE_OVERLOADING
    valueTable_type                         ,
#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.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.Gst.Callbacks as Gst.Callbacks

-- | Memory-managed wrapper type.
newtype ValueTable = ValueTable (ManagedPtr ValueTable)
instance WrappedPtr ValueTable where
    wrappedPtrCalloc = callocBytes 64
    wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 64 >=> wrapPtr ValueTable)
    wrappedPtrFree = Just ptr_to_g_free

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

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


-- | A convenience alias for `Nothing` :: `Maybe` `ValueTable`.
noValueTable :: Maybe ValueTable
noValueTable = Nothing

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

@
'Data.GI.Base.Attributes.get' valueTable #type
@
-}
getValueTableType :: MonadIO m => ValueTable -> m GType
getValueTableType s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO CGType
    let val' = GType val
    return val'

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

@
'Data.GI.Base.Attributes.set' valueTable [ #type 'Data.GI.Base.Attributes.:=' value ]
@
-}
setValueTableType :: MonadIO m => ValueTable -> GType -> m ()
setValueTableType s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = gtypeToCGType val
    poke (ptr `plusPtr` 0) (val' :: CGType)

#if ENABLE_OVERLOADING
data ValueTableTypeFieldInfo
instance AttrInfo ValueTableTypeFieldInfo where
    type AttrAllowedOps ValueTableTypeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ValueTableTypeFieldInfo = (~) GType
    type AttrBaseTypeConstraint ValueTableTypeFieldInfo = (~) ValueTable
    type AttrGetType ValueTableTypeFieldInfo = GType
    type AttrLabel ValueTableTypeFieldInfo = "type"
    type AttrOrigin ValueTableTypeFieldInfo = ValueTable
    attrGet _ = getValueTableType
    attrSet _ = setValueTableType
    attrConstruct = undefined
    attrClear _ = undefined

valueTable_type :: AttrLabelProxy "type"
valueTable_type = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' valueTable #compare
@
-}
getValueTableCompare :: MonadIO m => ValueTable -> m (Maybe Gst.Callbacks.ValueCompareFunc)
getValueTableCompare s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO (FunPtr Gst.Callbacks.C_ValueCompareFunc)
    result <- SP.convertFunPtrIfNonNull val $ \val' -> do
        let val'' = Gst.Callbacks.dynamic_ValueCompareFunc val'
        return val''
    return result

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

@
'Data.GI.Base.Attributes.set' valueTable [ #compare 'Data.GI.Base.Attributes.:=' value ]
@
-}
setValueTableCompare :: MonadIO m => ValueTable -> FunPtr Gst.Callbacks.C_ValueCompareFunc -> m ()
setValueTableCompare s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (val :: FunPtr Gst.Callbacks.C_ValueCompareFunc)

{- |
Set the value of the “@compare@” 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' #compare
@
-}
clearValueTableCompare :: MonadIO m => ValueTable -> m ()
clearValueTableCompare s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (FP.nullFunPtr :: FunPtr Gst.Callbacks.C_ValueCompareFunc)

#if ENABLE_OVERLOADING
data ValueTableCompareFieldInfo
instance AttrInfo ValueTableCompareFieldInfo where
    type AttrAllowedOps ValueTableCompareFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ValueTableCompareFieldInfo = (~) (FunPtr Gst.Callbacks.C_ValueCompareFunc)
    type AttrBaseTypeConstraint ValueTableCompareFieldInfo = (~) ValueTable
    type AttrGetType ValueTableCompareFieldInfo = Maybe Gst.Callbacks.ValueCompareFunc
    type AttrLabel ValueTableCompareFieldInfo = "compare"
    type AttrOrigin ValueTableCompareFieldInfo = ValueTable
    attrGet _ = getValueTableCompare
    attrSet _ = setValueTableCompare
    attrConstruct = undefined
    attrClear _ = clearValueTableCompare

valueTable_compare :: AttrLabelProxy "compare"
valueTable_compare = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' valueTable #serialize
@
-}
getValueTableSerialize :: MonadIO m => ValueTable -> m (Maybe Gst.Callbacks.ValueSerializeFunc)
getValueTableSerialize s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 16) :: IO (FunPtr Gst.Callbacks.C_ValueSerializeFunc)
    result <- SP.convertFunPtrIfNonNull val $ \val' -> do
        let val'' = Gst.Callbacks.dynamic_ValueSerializeFunc val'
        return val''
    return result

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

@
'Data.GI.Base.Attributes.set' valueTable [ #serialize 'Data.GI.Base.Attributes.:=' value ]
@
-}
setValueTableSerialize :: MonadIO m => ValueTable -> FunPtr Gst.Callbacks.C_ValueSerializeFunc -> m ()
setValueTableSerialize s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (val :: FunPtr Gst.Callbacks.C_ValueSerializeFunc)

{- |
Set the value of the “@serialize@” 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' #serialize
@
-}
clearValueTableSerialize :: MonadIO m => ValueTable -> m ()
clearValueTableSerialize s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (FP.nullFunPtr :: FunPtr Gst.Callbacks.C_ValueSerializeFunc)

#if ENABLE_OVERLOADING
data ValueTableSerializeFieldInfo
instance AttrInfo ValueTableSerializeFieldInfo where
    type AttrAllowedOps ValueTableSerializeFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ValueTableSerializeFieldInfo = (~) (FunPtr Gst.Callbacks.C_ValueSerializeFunc)
    type AttrBaseTypeConstraint ValueTableSerializeFieldInfo = (~) ValueTable
    type AttrGetType ValueTableSerializeFieldInfo = Maybe Gst.Callbacks.ValueSerializeFunc
    type AttrLabel ValueTableSerializeFieldInfo = "serialize"
    type AttrOrigin ValueTableSerializeFieldInfo = ValueTable
    attrGet _ = getValueTableSerialize
    attrSet _ = setValueTableSerialize
    attrConstruct = undefined
    attrClear _ = clearValueTableSerialize

valueTable_serialize :: AttrLabelProxy "serialize"
valueTable_serialize = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' valueTable #deserialize
@
-}
getValueTableDeserialize :: MonadIO m => ValueTable -> m (Maybe Gst.Callbacks.ValueDeserializeFunc)
getValueTableDeserialize s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 24) :: IO (FunPtr Gst.Callbacks.C_ValueDeserializeFunc)
    result <- SP.convertFunPtrIfNonNull val $ \val' -> do
        let val'' = Gst.Callbacks.dynamic_ValueDeserializeFunc val'
        return val''
    return result

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

@
'Data.GI.Base.Attributes.set' valueTable [ #deserialize 'Data.GI.Base.Attributes.:=' value ]
@
-}
setValueTableDeserialize :: MonadIO m => ValueTable -> FunPtr Gst.Callbacks.C_ValueDeserializeFunc -> m ()
setValueTableDeserialize s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 24) (val :: FunPtr Gst.Callbacks.C_ValueDeserializeFunc)

{- |
Set the value of the “@deserialize@” 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' #deserialize
@
-}
clearValueTableDeserialize :: MonadIO m => ValueTable -> m ()
clearValueTableDeserialize s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 24) (FP.nullFunPtr :: FunPtr Gst.Callbacks.C_ValueDeserializeFunc)

#if ENABLE_OVERLOADING
data ValueTableDeserializeFieldInfo
instance AttrInfo ValueTableDeserializeFieldInfo where
    type AttrAllowedOps ValueTableDeserializeFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ValueTableDeserializeFieldInfo = (~) (FunPtr Gst.Callbacks.C_ValueDeserializeFunc)
    type AttrBaseTypeConstraint ValueTableDeserializeFieldInfo = (~) ValueTable
    type AttrGetType ValueTableDeserializeFieldInfo = Maybe Gst.Callbacks.ValueDeserializeFunc
    type AttrLabel ValueTableDeserializeFieldInfo = "deserialize"
    type AttrOrigin ValueTableDeserializeFieldInfo = ValueTable
    attrGet _ = getValueTableDeserialize
    attrSet _ = setValueTableDeserialize
    attrConstruct = undefined
    attrClear _ = clearValueTableDeserialize

valueTable_deserialize :: AttrLabelProxy "deserialize"
valueTable_deserialize = AttrLabelProxy

#endif



#if ENABLE_OVERLOADING
instance O.HasAttributeList ValueTable
type instance O.AttributeList ValueTable = ValueTableAttributeList
type ValueTableAttributeList = ('[ '("type", ValueTableTypeFieldInfo), '("compare", ValueTableCompareFieldInfo), '("serialize", ValueTableSerializeFieldInfo), '("deserialize", ValueTableDeserializeFieldInfo)] :: [(Symbol, *)])
#endif

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

instance (info ~ ResolveValueTableMethod t ValueTable, O.MethodInfo info ValueTable p) => OL.IsLabel t (ValueTable -> 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