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

Parameters passed to the 'GI.Gst.Objects.BufferPool.bufferPoolAcquireBuffer' function to control the
allocation of the buffer.

The default implementation ignores the /@start@/ and /@stop@/ members but other
implementations can use this extra information to decide what buffer to
return.
-}

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

module GI.Gst.Structs.BufferPoolAcquireParams
    (

-- * Exported types
    BufferPoolAcquireParams(..)             ,
    newZeroBufferPoolAcquireParams          ,
    noBufferPoolAcquireParams               ,


 -- * Properties
-- ** flags #attr:flags#
{- | additional flags
-}
#if ENABLE_OVERLOADING
    bufferPoolAcquireParams_flags           ,
#endif
    getBufferPoolAcquireParamsFlags         ,
    setBufferPoolAcquireParamsFlags         ,


-- ** format #attr:format#
{- | the format of /@start@/ and /@stop@/
-}
#if ENABLE_OVERLOADING
    bufferPoolAcquireParams_format          ,
#endif
    getBufferPoolAcquireParamsFormat        ,
    setBufferPoolAcquireParamsFormat        ,


-- ** start #attr:start#
{- | the start position
-}
#if ENABLE_OVERLOADING
    bufferPoolAcquireParams_start           ,
#endif
    getBufferPoolAcquireParamsStart         ,
    setBufferPoolAcquireParamsStart         ,


-- ** stop #attr:stop#
{- | the stop position
-}
#if ENABLE_OVERLOADING
    bufferPoolAcquireParams_stop            ,
#endif
    getBufferPoolAcquireParamsStop          ,
    setBufferPoolAcquireParamsStop          ,




    ) 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 {-# SOURCE #-} qualified GI.Gst.Enums as Gst.Enums
import {-# SOURCE #-} qualified GI.Gst.Flags as Gst.Flags

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

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

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


-- | A convenience alias for `Nothing` :: `Maybe` `BufferPoolAcquireParams`.
noBufferPoolAcquireParams :: Maybe BufferPoolAcquireParams
noBufferPoolAcquireParams = Nothing

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

@
'Data.GI.Base.Attributes.get' bufferPoolAcquireParams #format
@
-}
getBufferPoolAcquireParamsFormat :: MonadIO m => BufferPoolAcquireParams -> m Gst.Enums.Format
getBufferPoolAcquireParamsFormat s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO CUInt
    let val' = (toEnum . fromIntegral) val
    return val'

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

@
'Data.GI.Base.Attributes.set' bufferPoolAcquireParams [ #format 'Data.GI.Base.Attributes.:=' value ]
@
-}
setBufferPoolAcquireParamsFormat :: MonadIO m => BufferPoolAcquireParams -> Gst.Enums.Format -> m ()
setBufferPoolAcquireParamsFormat s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 0) (val' :: CUInt)

#if ENABLE_OVERLOADING
data BufferPoolAcquireParamsFormatFieldInfo
instance AttrInfo BufferPoolAcquireParamsFormatFieldInfo where
    type AttrAllowedOps BufferPoolAcquireParamsFormatFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint BufferPoolAcquireParamsFormatFieldInfo = (~) Gst.Enums.Format
    type AttrBaseTypeConstraint BufferPoolAcquireParamsFormatFieldInfo = (~) BufferPoolAcquireParams
    type AttrGetType BufferPoolAcquireParamsFormatFieldInfo = Gst.Enums.Format
    type AttrLabel BufferPoolAcquireParamsFormatFieldInfo = "format"
    type AttrOrigin BufferPoolAcquireParamsFormatFieldInfo = BufferPoolAcquireParams
    attrGet _ = getBufferPoolAcquireParamsFormat
    attrSet _ = setBufferPoolAcquireParamsFormat
    attrConstruct = undefined
    attrClear _ = undefined

bufferPoolAcquireParams_format :: AttrLabelProxy "format"
bufferPoolAcquireParams_format = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' bufferPoolAcquireParams #start
@
-}
getBufferPoolAcquireParamsStart :: MonadIO m => BufferPoolAcquireParams -> m Int64
getBufferPoolAcquireParamsStart s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO Int64
    return val

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

@
'Data.GI.Base.Attributes.set' bufferPoolAcquireParams [ #start 'Data.GI.Base.Attributes.:=' value ]
@
-}
setBufferPoolAcquireParamsStart :: MonadIO m => BufferPoolAcquireParams -> Int64 -> m ()
setBufferPoolAcquireParamsStart s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (val :: Int64)

#if ENABLE_OVERLOADING
data BufferPoolAcquireParamsStartFieldInfo
instance AttrInfo BufferPoolAcquireParamsStartFieldInfo where
    type AttrAllowedOps BufferPoolAcquireParamsStartFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint BufferPoolAcquireParamsStartFieldInfo = (~) Int64
    type AttrBaseTypeConstraint BufferPoolAcquireParamsStartFieldInfo = (~) BufferPoolAcquireParams
    type AttrGetType BufferPoolAcquireParamsStartFieldInfo = Int64
    type AttrLabel BufferPoolAcquireParamsStartFieldInfo = "start"
    type AttrOrigin BufferPoolAcquireParamsStartFieldInfo = BufferPoolAcquireParams
    attrGet _ = getBufferPoolAcquireParamsStart
    attrSet _ = setBufferPoolAcquireParamsStart
    attrConstruct = undefined
    attrClear _ = undefined

bufferPoolAcquireParams_start :: AttrLabelProxy "start"
bufferPoolAcquireParams_start = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' bufferPoolAcquireParams #stop
@
-}
getBufferPoolAcquireParamsStop :: MonadIO m => BufferPoolAcquireParams -> m Int64
getBufferPoolAcquireParamsStop s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 16) :: IO Int64
    return val

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

@
'Data.GI.Base.Attributes.set' bufferPoolAcquireParams [ #stop 'Data.GI.Base.Attributes.:=' value ]
@
-}
setBufferPoolAcquireParamsStop :: MonadIO m => BufferPoolAcquireParams -> Int64 -> m ()
setBufferPoolAcquireParamsStop s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (val :: Int64)

#if ENABLE_OVERLOADING
data BufferPoolAcquireParamsStopFieldInfo
instance AttrInfo BufferPoolAcquireParamsStopFieldInfo where
    type AttrAllowedOps BufferPoolAcquireParamsStopFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint BufferPoolAcquireParamsStopFieldInfo = (~) Int64
    type AttrBaseTypeConstraint BufferPoolAcquireParamsStopFieldInfo = (~) BufferPoolAcquireParams
    type AttrGetType BufferPoolAcquireParamsStopFieldInfo = Int64
    type AttrLabel BufferPoolAcquireParamsStopFieldInfo = "stop"
    type AttrOrigin BufferPoolAcquireParamsStopFieldInfo = BufferPoolAcquireParams
    attrGet _ = getBufferPoolAcquireParamsStop
    attrSet _ = setBufferPoolAcquireParamsStop
    attrConstruct = undefined
    attrClear _ = undefined

bufferPoolAcquireParams_stop :: AttrLabelProxy "stop"
bufferPoolAcquireParams_stop = 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' bufferPoolAcquireParams #flags
@
-}
getBufferPoolAcquireParamsFlags :: MonadIO m => BufferPoolAcquireParams -> m [Gst.Flags.BufferPoolAcquireFlags]
getBufferPoolAcquireParamsFlags s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 24) :: IO CUInt
    let val' = wordToGFlags val
    return 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' bufferPoolAcquireParams [ #flags 'Data.GI.Base.Attributes.:=' value ]
@
-}
setBufferPoolAcquireParamsFlags :: MonadIO m => BufferPoolAcquireParams -> [Gst.Flags.BufferPoolAcquireFlags] -> m ()
setBufferPoolAcquireParamsFlags s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = gflagsToWord val
    poke (ptr `plusPtr` 24) (val' :: CUInt)

#if ENABLE_OVERLOADING
data BufferPoolAcquireParamsFlagsFieldInfo
instance AttrInfo BufferPoolAcquireParamsFlagsFieldInfo where
    type AttrAllowedOps BufferPoolAcquireParamsFlagsFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint BufferPoolAcquireParamsFlagsFieldInfo = (~) [Gst.Flags.BufferPoolAcquireFlags]
    type AttrBaseTypeConstraint BufferPoolAcquireParamsFlagsFieldInfo = (~) BufferPoolAcquireParams
    type AttrGetType BufferPoolAcquireParamsFlagsFieldInfo = [Gst.Flags.BufferPoolAcquireFlags]
    type AttrLabel BufferPoolAcquireParamsFlagsFieldInfo = "flags"
    type AttrOrigin BufferPoolAcquireParamsFlagsFieldInfo = BufferPoolAcquireParams
    attrGet _ = getBufferPoolAcquireParamsFlags
    attrSet _ = setBufferPoolAcquireParamsFlags
    attrConstruct = undefined
    attrClear _ = undefined

bufferPoolAcquireParams_flags :: AttrLabelProxy "flags"
bufferPoolAcquireParams_flags = AttrLabelProxy

#endif



#if ENABLE_OVERLOADING
instance O.HasAttributeList BufferPoolAcquireParams
type instance O.AttributeList BufferPoolAcquireParams = BufferPoolAcquireParamsAttributeList
type BufferPoolAcquireParamsAttributeList = ('[ '("format", BufferPoolAcquireParamsFormatFieldInfo), '("start", BufferPoolAcquireParamsStartFieldInfo), '("stop", BufferPoolAcquireParamsStopFieldInfo), '("flags", BufferPoolAcquireParamsFlagsFieldInfo)] :: [(Symbol, *)])
#endif

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

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