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

Virtual table for handling properties and method calls for a D-Bus
interface.

Since 2.38, if you want to handle getting\/setting D-Bus properties
asynchronously, give 'Nothing' as your @/get_property()/@ or @/set_property()/@
function. The D-Bus call will be directed to your /@methodCall@/ function,
with the provided /@interfaceName@/ set to \"org.freedesktop.DBus.Properties\".

Ownership of the 'GI.Gio.Objects.DBusMethodInvocation.DBusMethodInvocation' object passed to the
@/method_call()/@ function is transferred to your handler; you must
call one of the methods of 'GI.Gio.Objects.DBusMethodInvocation.DBusMethodInvocation' to return a reply
(possibly empty), or an error. These functions also take ownership
of the passed-in invocation object, so unless the invocation
object has otherwise been referenced, it will be then be freed.
Calling one of these functions may be done within your
@/method_call()/@ implementation but it also can be done at a later
point to handle the method asynchronously.

The usual checks on the validity of the calls is performed. For
@Get@ calls, an error is automatically returned if the property does
not exist or the permissions do not allow access. The same checks are
performed for @Set@ calls, and the provided value is also checked for
being the correct type.

For both @Get@ and @Set@ calls, the 'GI.Gio.Objects.DBusMethodInvocation.DBusMethodInvocation'
passed to the /@methodCall@/ handler can be queried with
'GI.Gio.Objects.DBusMethodInvocation.dBusMethodInvocationGetPropertyInfo' to get a pointer
to the 'GI.Gio.Structs.DBusPropertyInfo.DBusPropertyInfo' of the property.

If you have readable properties specified in your interface info,
you must ensure that you either provide a non-'Nothing' /@getProperty@/()
function or provide implementations of both the @Get@ and @GetAll@
methods on org.freedesktop.DBus.Properties interface in your /@methodCall@/
function. Note that the required return type of the @Get@ call is
@(v)@, not the type of the property. @GetAll@ expects a return value
of type @a{sv}@.

If you have writable properties specified in your interface info,
you must ensure that you either provide a non-'Nothing' /@setProperty@/()
function or provide an implementation of the @Set@ call. If implementing
the call, you must return the value of type @/G_VARIANT_TYPE_UNIT/@.

/Since: 2.26/
-}

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

module GI.Gio.Structs.DBusInterfaceVTable
    (

-- * Exported types
    DBusInterfaceVTable(..)                 ,
    newZeroDBusInterfaceVTable              ,
    noDBusInterfaceVTable                   ,


 -- * Properties
-- ** getProperty #attr:getProperty#
{- | Function for getting a property.
-}
    clearDBusInterfaceVTableGetProperty     ,
#if ENABLE_OVERLOADING
    dBusInterfaceVTable_getProperty         ,
#endif
    getDBusInterfaceVTableGetProperty       ,
    setDBusInterfaceVTableGetProperty       ,


-- ** methodCall #attr:methodCall#
{- | Function for handling incoming method calls.
-}
    clearDBusInterfaceVTableMethodCall      ,
#if ENABLE_OVERLOADING
    dBusInterfaceVTable_methodCall          ,
#endif
    getDBusInterfaceVTableMethodCall        ,
    setDBusInterfaceVTableMethodCall        ,


-- ** setProperty #attr:setProperty#
{- | Function for setting a property.
-}
    clearDBusInterfaceVTableSetProperty     ,
#if ENABLE_OVERLOADING
    dBusInterfaceVTable_setProperty         ,
#endif
    getDBusInterfaceVTableSetProperty       ,
    setDBusInterfaceVTableSetProperty       ,




    ) 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.Gio.Callbacks as Gio.Callbacks

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

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

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


-- | A convenience alias for `Nothing` :: `Maybe` `DBusInterfaceVTable`.
noDBusInterfaceVTable :: Maybe DBusInterfaceVTable
noDBusInterfaceVTable = Nothing

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

@
'Data.GI.Base.Attributes.get' dBusInterfaceVTable #methodCall
@
-}
getDBusInterfaceVTableMethodCall :: MonadIO m => DBusInterfaceVTable -> m (Maybe Gio.Callbacks.DBusInterfaceMethodCallFunc_WithClosures)
getDBusInterfaceVTableMethodCall s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO (FunPtr Gio.Callbacks.C_DBusInterfaceMethodCallFunc)
    result <- SP.convertFunPtrIfNonNull val $ \val' -> do
        let val'' = Gio.Callbacks.dynamic_DBusInterfaceMethodCallFunc val'
        return val''
    return result

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

@
'Data.GI.Base.Attributes.set' dBusInterfaceVTable [ #methodCall 'Data.GI.Base.Attributes.:=' value ]
@
-}
setDBusInterfaceVTableMethodCall :: MonadIO m => DBusInterfaceVTable -> FunPtr Gio.Callbacks.C_DBusInterfaceMethodCallFunc -> m ()
setDBusInterfaceVTableMethodCall s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (val :: FunPtr Gio.Callbacks.C_DBusInterfaceMethodCallFunc)

{- |
Set the value of the “@method_call@” 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' #methodCall
@
-}
clearDBusInterfaceVTableMethodCall :: MonadIO m => DBusInterfaceVTable -> m ()
clearDBusInterfaceVTableMethodCall s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (FP.nullFunPtr :: FunPtr Gio.Callbacks.C_DBusInterfaceMethodCallFunc)

#if ENABLE_OVERLOADING
data DBusInterfaceVTableMethodCallFieldInfo
instance AttrInfo DBusInterfaceVTableMethodCallFieldInfo where
    type AttrAllowedOps DBusInterfaceVTableMethodCallFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint DBusInterfaceVTableMethodCallFieldInfo = (~) (FunPtr Gio.Callbacks.C_DBusInterfaceMethodCallFunc)
    type AttrBaseTypeConstraint DBusInterfaceVTableMethodCallFieldInfo = (~) DBusInterfaceVTable
    type AttrGetType DBusInterfaceVTableMethodCallFieldInfo = Maybe Gio.Callbacks.DBusInterfaceMethodCallFunc_WithClosures
    type AttrLabel DBusInterfaceVTableMethodCallFieldInfo = "method_call"
    type AttrOrigin DBusInterfaceVTableMethodCallFieldInfo = DBusInterfaceVTable
    attrGet _ = getDBusInterfaceVTableMethodCall
    attrSet _ = setDBusInterfaceVTableMethodCall
    attrConstruct = undefined
    attrClear _ = clearDBusInterfaceVTableMethodCall

dBusInterfaceVTable_methodCall :: AttrLabelProxy "methodCall"
dBusInterfaceVTable_methodCall = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' dBusInterfaceVTable #getProperty
@
-}
getDBusInterfaceVTableGetProperty :: MonadIO m => DBusInterfaceVTable -> m (Maybe Gio.Callbacks.DBusInterfaceGetPropertyFunc_WithClosures)
getDBusInterfaceVTableGetProperty s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO (FunPtr Gio.Callbacks.C_DBusInterfaceGetPropertyFunc)
    result <- SP.convertFunPtrIfNonNull val $ \val' -> do
        let val'' = Gio.Callbacks.dynamic_DBusInterfaceGetPropertyFunc val'
        return val''
    return result

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

@
'Data.GI.Base.Attributes.set' dBusInterfaceVTable [ #getProperty 'Data.GI.Base.Attributes.:=' value ]
@
-}
setDBusInterfaceVTableGetProperty :: MonadIO m => DBusInterfaceVTable -> FunPtr Gio.Callbacks.C_DBusInterfaceGetPropertyFunc -> m ()
setDBusInterfaceVTableGetProperty s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (val :: FunPtr Gio.Callbacks.C_DBusInterfaceGetPropertyFunc)

{- |
Set the value of the “@get_property@” 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' #getProperty
@
-}
clearDBusInterfaceVTableGetProperty :: MonadIO m => DBusInterfaceVTable -> m ()
clearDBusInterfaceVTableGetProperty s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (FP.nullFunPtr :: FunPtr Gio.Callbacks.C_DBusInterfaceGetPropertyFunc)

#if ENABLE_OVERLOADING
data DBusInterfaceVTableGetPropertyFieldInfo
instance AttrInfo DBusInterfaceVTableGetPropertyFieldInfo where
    type AttrAllowedOps DBusInterfaceVTableGetPropertyFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint DBusInterfaceVTableGetPropertyFieldInfo = (~) (FunPtr Gio.Callbacks.C_DBusInterfaceGetPropertyFunc)
    type AttrBaseTypeConstraint DBusInterfaceVTableGetPropertyFieldInfo = (~) DBusInterfaceVTable
    type AttrGetType DBusInterfaceVTableGetPropertyFieldInfo = Maybe Gio.Callbacks.DBusInterfaceGetPropertyFunc_WithClosures
    type AttrLabel DBusInterfaceVTableGetPropertyFieldInfo = "get_property"
    type AttrOrigin DBusInterfaceVTableGetPropertyFieldInfo = DBusInterfaceVTable
    attrGet _ = getDBusInterfaceVTableGetProperty
    attrSet _ = setDBusInterfaceVTableGetProperty
    attrConstruct = undefined
    attrClear _ = clearDBusInterfaceVTableGetProperty

dBusInterfaceVTable_getProperty :: AttrLabelProxy "getProperty"
dBusInterfaceVTable_getProperty = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' dBusInterfaceVTable #setProperty
@
-}
getDBusInterfaceVTableSetProperty :: MonadIO m => DBusInterfaceVTable -> m (Maybe Gio.Callbacks.DBusInterfaceSetPropertyFunc_WithClosures)
getDBusInterfaceVTableSetProperty s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 16) :: IO (FunPtr Gio.Callbacks.C_DBusInterfaceSetPropertyFunc)
    result <- SP.convertFunPtrIfNonNull val $ \val' -> do
        let val'' = Gio.Callbacks.dynamic_DBusInterfaceSetPropertyFunc val'
        return val''
    return result

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

@
'Data.GI.Base.Attributes.set' dBusInterfaceVTable [ #setProperty 'Data.GI.Base.Attributes.:=' value ]
@
-}
setDBusInterfaceVTableSetProperty :: MonadIO m => DBusInterfaceVTable -> FunPtr Gio.Callbacks.C_DBusInterfaceSetPropertyFunc -> m ()
setDBusInterfaceVTableSetProperty s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (val :: FunPtr Gio.Callbacks.C_DBusInterfaceSetPropertyFunc)

{- |
Set the value of the “@set_property@” 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' #setProperty
@
-}
clearDBusInterfaceVTableSetProperty :: MonadIO m => DBusInterfaceVTable -> m ()
clearDBusInterfaceVTableSetProperty s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (FP.nullFunPtr :: FunPtr Gio.Callbacks.C_DBusInterfaceSetPropertyFunc)

#if ENABLE_OVERLOADING
data DBusInterfaceVTableSetPropertyFieldInfo
instance AttrInfo DBusInterfaceVTableSetPropertyFieldInfo where
    type AttrAllowedOps DBusInterfaceVTableSetPropertyFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint DBusInterfaceVTableSetPropertyFieldInfo = (~) (FunPtr Gio.Callbacks.C_DBusInterfaceSetPropertyFunc)
    type AttrBaseTypeConstraint DBusInterfaceVTableSetPropertyFieldInfo = (~) DBusInterfaceVTable
    type AttrGetType DBusInterfaceVTableSetPropertyFieldInfo = Maybe Gio.Callbacks.DBusInterfaceSetPropertyFunc_WithClosures
    type AttrLabel DBusInterfaceVTableSetPropertyFieldInfo = "set_property"
    type AttrOrigin DBusInterfaceVTableSetPropertyFieldInfo = DBusInterfaceVTable
    attrGet _ = getDBusInterfaceVTableSetProperty
    attrSet _ = setDBusInterfaceVTableSetProperty
    attrConstruct = undefined
    attrClear _ = clearDBusInterfaceVTableSetProperty

dBusInterfaceVTable_setProperty :: AttrLabelProxy "setProperty"
dBusInterfaceVTable_setProperty = AttrLabelProxy

#endif



#if ENABLE_OVERLOADING
instance O.HasAttributeList DBusInterfaceVTable
type instance O.AttributeList DBusInterfaceVTable = DBusInterfaceVTableAttributeList
type DBusInterfaceVTableAttributeList = ('[ '("methodCall", DBusInterfaceVTableMethodCallFieldInfo), '("getProperty", DBusInterfaceVTableGetPropertyFieldInfo), '("setProperty", DBusInterfaceVTableSetPropertyFieldInfo)] :: [(Symbol, *)])
#endif

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

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