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

The GObjectConstructParam struct is an auxiliary
structure used to hand 'GI.GObject.Objects.ParamSpec.ParamSpec'\/'GI.GObject.Structs.Value.Value' pairs to the /@constructor@/ of
a 'GI.GObject.Structs.ObjectClass.ObjectClass'.
-}

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

module GI.GObject.Structs.ObjectConstructParam
    (

-- * Exported types
    ObjectConstructParam(..)                ,
    newZeroObjectConstructParam             ,
    noObjectConstructParam                  ,


 -- * Properties
-- ** pspec #attr:pspec#
{- | the 'GI.GObject.Objects.ParamSpec.ParamSpec' of the construct parameter
-}
    clearObjectConstructParamPspec          ,
    getObjectConstructParamPspec            ,
#if ENABLE_OVERLOADING
    objectConstructParam_pspec              ,
#endif
    setObjectConstructParamPspec            ,


-- ** value #attr:value#
{- | the value to set the parameter to
-}
    clearObjectConstructParamValue          ,
    getObjectConstructParamValue            ,
#if ENABLE_OVERLOADING
    objectConstructParam_value              ,
#endif
    setObjectConstructParamValue            ,




    ) 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


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

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

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


-- | A convenience alias for `Nothing` :: `Maybe` `ObjectConstructParam`.
noObjectConstructParam :: Maybe ObjectConstructParam
noObjectConstructParam = Nothing

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

@
'Data.GI.Base.Attributes.get' objectConstructParam #pspec
@
-}
getObjectConstructParamPspec :: MonadIO m => ObjectConstructParam -> m (Maybe GParamSpec)
getObjectConstructParamPspec s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO (Ptr GParamSpec)
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- B.GParamSpec.newGParamSpecFromPtr val'
        return val''
    return result

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

@
'Data.GI.Base.Attributes.set' objectConstructParam [ #pspec 'Data.GI.Base.Attributes.:=' value ]
@
-}
setObjectConstructParamPspec :: MonadIO m => ObjectConstructParam -> Ptr GParamSpec -> m ()
setObjectConstructParamPspec s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (val :: Ptr GParamSpec)

{- |
Set the value of the “@pspec@” 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' #pspec
@
-}
clearObjectConstructParamPspec :: MonadIO m => ObjectConstructParam -> m ()
clearObjectConstructParamPspec s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (FP.nullPtr :: Ptr GParamSpec)

#if ENABLE_OVERLOADING
data ObjectConstructParamPspecFieldInfo
instance AttrInfo ObjectConstructParamPspecFieldInfo where
    type AttrAllowedOps ObjectConstructParamPspecFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ObjectConstructParamPspecFieldInfo = (~) (Ptr GParamSpec)
    type AttrBaseTypeConstraint ObjectConstructParamPspecFieldInfo = (~) ObjectConstructParam
    type AttrGetType ObjectConstructParamPspecFieldInfo = Maybe GParamSpec
    type AttrLabel ObjectConstructParamPspecFieldInfo = "pspec"
    type AttrOrigin ObjectConstructParamPspecFieldInfo = ObjectConstructParam
    attrGet _ = getObjectConstructParamPspec
    attrSet _ = setObjectConstructParamPspec
    attrConstruct = undefined
    attrClear _ = clearObjectConstructParamPspec

objectConstructParam_pspec :: AttrLabelProxy "pspec"
objectConstructParam_pspec = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' objectConstructParam #value
@
-}
getObjectConstructParamValue :: MonadIO m => ObjectConstructParam -> m (Maybe GValue)
getObjectConstructParamValue s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO (Ptr GValue)
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- (newBoxed GValue) val'
        return val''
    return result

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

@
'Data.GI.Base.Attributes.set' objectConstructParam [ #value 'Data.GI.Base.Attributes.:=' value ]
@
-}
setObjectConstructParamValue :: MonadIO m => ObjectConstructParam -> Ptr GValue -> m ()
setObjectConstructParamValue s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (val :: Ptr GValue)

{- |
Set the value of the “@value@” 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' #value
@
-}
clearObjectConstructParamValue :: MonadIO m => ObjectConstructParam -> m ()
clearObjectConstructParamValue s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (FP.nullPtr :: Ptr GValue)

#if ENABLE_OVERLOADING
data ObjectConstructParamValueFieldInfo
instance AttrInfo ObjectConstructParamValueFieldInfo where
    type AttrAllowedOps ObjectConstructParamValueFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ObjectConstructParamValueFieldInfo = (~) (Ptr GValue)
    type AttrBaseTypeConstraint ObjectConstructParamValueFieldInfo = (~) ObjectConstructParam
    type AttrGetType ObjectConstructParamValueFieldInfo = Maybe GValue
    type AttrLabel ObjectConstructParamValueFieldInfo = "value"
    type AttrOrigin ObjectConstructParamValueFieldInfo = ObjectConstructParam
    attrGet _ = getObjectConstructParamValue
    attrSet _ = setObjectConstructParamValue
    attrConstruct = undefined
    attrClear _ = clearObjectConstructParamValue

objectConstructParam_value :: AttrLabelProxy "value"
objectConstructParam_value = AttrLabelProxy

#endif



#if ENABLE_OVERLOADING
instance O.HasAttributeList ObjectConstructParam
type instance O.AttributeList ObjectConstructParam = ObjectConstructParamAttributeList
type ObjectConstructParamAttributeList = ('[ '("pspec", ObjectConstructParamPspecFieldInfo), '("value", ObjectConstructParamValueFieldInfo)] :: [(Symbol, *)])
#endif

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

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