{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gst.Structs.BufferPoolAcquireParams
(
BufferPoolAcquireParams(..) ,
newZeroBufferPoolAcquireParams ,
#if defined(ENABLE_OVERLOADING)
ResolveBufferPoolAcquireParamsMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
bufferPoolAcquireParams_flags ,
#endif
getBufferPoolAcquireParamsFlags ,
setBufferPoolAcquireParamsFlags ,
#if defined(ENABLE_OVERLOADING)
bufferPoolAcquireParams_format ,
#endif
getBufferPoolAcquireParamsFormat ,
setBufferPoolAcquireParamsFormat ,
#if defined(ENABLE_OVERLOADING)
bufferPoolAcquireParams_start ,
#endif
getBufferPoolAcquireParamsStart ,
setBufferPoolAcquireParamsStart ,
#if defined(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.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.GHashTable as B.GHT
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.Coerce as Coerce
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 GHC.Records as R
import {-# SOURCE #-} qualified GI.Gst.Enums as Gst.Enums
import {-# SOURCE #-} qualified GI.Gst.Flags as Gst.Flags
newtype BufferPoolAcquireParams = BufferPoolAcquireParams (SP.ManagedPtr BufferPoolAcquireParams)
deriving (BufferPoolAcquireParams -> BufferPoolAcquireParams -> Bool
(BufferPoolAcquireParams -> BufferPoolAcquireParams -> Bool)
-> (BufferPoolAcquireParams -> BufferPoolAcquireParams -> Bool)
-> Eq BufferPoolAcquireParams
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BufferPoolAcquireParams -> BufferPoolAcquireParams -> Bool
== :: BufferPoolAcquireParams -> BufferPoolAcquireParams -> Bool
$c/= :: BufferPoolAcquireParams -> BufferPoolAcquireParams -> Bool
/= :: BufferPoolAcquireParams -> BufferPoolAcquireParams -> Bool
Eq)
instance SP.ManagedPtrNewtype BufferPoolAcquireParams where
toManagedPtr :: BufferPoolAcquireParams -> ManagedPtr BufferPoolAcquireParams
toManagedPtr (BufferPoolAcquireParams ManagedPtr BufferPoolAcquireParams
p) = ManagedPtr BufferPoolAcquireParams
p
instance BoxedPtr BufferPoolAcquireParams where
boxedPtrCopy :: BufferPoolAcquireParams -> IO BufferPoolAcquireParams
boxedPtrCopy = \BufferPoolAcquireParams
p -> BufferPoolAcquireParams
-> (Ptr BufferPoolAcquireParams -> IO BufferPoolAcquireParams)
-> IO BufferPoolAcquireParams
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr BufferPoolAcquireParams
p (Int
-> Ptr BufferPoolAcquireParams -> IO (Ptr BufferPoolAcquireParams)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
64 (Ptr BufferPoolAcquireParams -> IO (Ptr BufferPoolAcquireParams))
-> (Ptr BufferPoolAcquireParams -> IO BufferPoolAcquireParams)
-> Ptr BufferPoolAcquireParams
-> IO BufferPoolAcquireParams
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr BufferPoolAcquireParams -> BufferPoolAcquireParams)
-> Ptr BufferPoolAcquireParams -> IO BufferPoolAcquireParams
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr BufferPoolAcquireParams -> BufferPoolAcquireParams
BufferPoolAcquireParams)
boxedPtrFree :: BufferPoolAcquireParams -> IO ()
boxedPtrFree = \BufferPoolAcquireParams
x -> BufferPoolAcquireParams
-> (Ptr BufferPoolAcquireParams -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr BufferPoolAcquireParams
x Ptr BufferPoolAcquireParams -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr BufferPoolAcquireParams where
boxedPtrCalloc :: IO (Ptr BufferPoolAcquireParams)
boxedPtrCalloc = Int -> IO (Ptr BufferPoolAcquireParams)
forall a. Int -> IO (Ptr a)
callocBytes Int
64
newZeroBufferPoolAcquireParams :: MonadIO m => m BufferPoolAcquireParams
newZeroBufferPoolAcquireParams :: forall (m :: * -> *). MonadIO m => m BufferPoolAcquireParams
newZeroBufferPoolAcquireParams = IO BufferPoolAcquireParams -> m BufferPoolAcquireParams
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO BufferPoolAcquireParams -> m BufferPoolAcquireParams)
-> IO BufferPoolAcquireParams -> m BufferPoolAcquireParams
forall a b. (a -> b) -> a -> b
$ IO (Ptr BufferPoolAcquireParams)
forall a. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr BufferPoolAcquireParams)
-> (Ptr BufferPoolAcquireParams -> IO BufferPoolAcquireParams)
-> IO BufferPoolAcquireParams
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr BufferPoolAcquireParams -> BufferPoolAcquireParams)
-> Ptr BufferPoolAcquireParams -> IO BufferPoolAcquireParams
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr BufferPoolAcquireParams -> BufferPoolAcquireParams
BufferPoolAcquireParams
instance tag ~ 'AttrSet => Constructible BufferPoolAcquireParams tag where
new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr BufferPoolAcquireParams -> BufferPoolAcquireParams)
-> [AttrOp BufferPoolAcquireParams tag]
-> m BufferPoolAcquireParams
new ManagedPtr BufferPoolAcquireParams -> BufferPoolAcquireParams
_ [AttrOp BufferPoolAcquireParams tag]
attrs = do
BufferPoolAcquireParams
o <- m BufferPoolAcquireParams
forall (m :: * -> *). MonadIO m => m BufferPoolAcquireParams
newZeroBufferPoolAcquireParams
BufferPoolAcquireParams
-> [AttrOp BufferPoolAcquireParams 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set BufferPoolAcquireParams
o [AttrOp BufferPoolAcquireParams tag]
[AttrOp BufferPoolAcquireParams 'AttrSet]
attrs
BufferPoolAcquireParams -> m BufferPoolAcquireParams
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return BufferPoolAcquireParams
o
getBufferPoolAcquireParamsFormat :: MonadIO m => BufferPoolAcquireParams -> m Gst.Enums.Format
getBufferPoolAcquireParamsFormat :: forall (m :: * -> *).
MonadIO m =>
BufferPoolAcquireParams -> m Format
getBufferPoolAcquireParamsFormat BufferPoolAcquireParams
s = IO Format -> m Format
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Format -> m Format) -> IO Format -> m Format
forall a b. (a -> b) -> a -> b
$ BufferPoolAcquireParams
-> (Ptr BufferPoolAcquireParams -> IO Format) -> IO Format
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr BufferPoolAcquireParams
s ((Ptr BufferPoolAcquireParams -> IO Format) -> IO Format)
-> (Ptr BufferPoolAcquireParams -> IO Format) -> IO Format
forall a b. (a -> b) -> a -> b
$ \Ptr BufferPoolAcquireParams
ptr -> do
CUInt
val <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr BufferPoolAcquireParams
ptr Ptr BufferPoolAcquireParams -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO CUInt
let val' :: Format
val' = (Int -> Format
forall a. Enum a => Int -> a
toEnum (Int -> Format) -> (CUInt -> Int) -> CUInt -> Format
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
val
Format -> IO Format
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Format
val'
setBufferPoolAcquireParamsFormat :: MonadIO m => BufferPoolAcquireParams -> Gst.Enums.Format -> m ()
setBufferPoolAcquireParamsFormat :: forall (m :: * -> *).
MonadIO m =>
BufferPoolAcquireParams -> Format -> m ()
setBufferPoolAcquireParamsFormat BufferPoolAcquireParams
s Format
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ BufferPoolAcquireParams
-> (Ptr BufferPoolAcquireParams -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr BufferPoolAcquireParams
s ((Ptr BufferPoolAcquireParams -> IO ()) -> IO ())
-> (Ptr BufferPoolAcquireParams -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr BufferPoolAcquireParams
ptr -> do
let val' :: CUInt
val' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (Format -> Int) -> Format -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Format -> Int
forall a. Enum a => a -> Int
fromEnum) Format
val
Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr BufferPoolAcquireParams
ptr Ptr BufferPoolAcquireParams -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (CUInt
val' :: CUInt)
#if defined(ENABLE_OVERLOADING)
data BufferPoolAcquireParamsFormatFieldInfo
instance AttrInfo BufferPoolAcquireParamsFormatFieldInfo where
type AttrBaseTypeConstraint BufferPoolAcquireParamsFormatFieldInfo = (~) BufferPoolAcquireParams
type AttrAllowedOps BufferPoolAcquireParamsFormatFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint BufferPoolAcquireParamsFormatFieldInfo = (~) Gst.Enums.Format
type AttrTransferTypeConstraint BufferPoolAcquireParamsFormatFieldInfo = (~)Gst.Enums.Format
type AttrTransferType BufferPoolAcquireParamsFormatFieldInfo = Gst.Enums.Format
type AttrGetType BufferPoolAcquireParamsFormatFieldInfo = Gst.Enums.Format
type AttrLabel BufferPoolAcquireParamsFormatFieldInfo = "format"
type AttrOrigin BufferPoolAcquireParamsFormatFieldInfo = BufferPoolAcquireParams
attrGet = getBufferPoolAcquireParamsFormat
attrSet = setBufferPoolAcquireParamsFormat
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gst.Structs.BufferPoolAcquireParams.format"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.26/docs/GI-Gst-Structs-BufferPoolAcquireParams.html#g:attr:format"
})
bufferPoolAcquireParams_format :: AttrLabelProxy "format"
bufferPoolAcquireParams_format = AttrLabelProxy
#endif
getBufferPoolAcquireParamsStart :: MonadIO m => BufferPoolAcquireParams -> m Int64
getBufferPoolAcquireParamsStart :: forall (m :: * -> *).
MonadIO m =>
BufferPoolAcquireParams -> m Int64
getBufferPoolAcquireParamsStart BufferPoolAcquireParams
s = IO Int64 -> m Int64
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int64 -> m Int64) -> IO Int64 -> m Int64
forall a b. (a -> b) -> a -> b
$ BufferPoolAcquireParams
-> (Ptr BufferPoolAcquireParams -> IO Int64) -> IO Int64
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr BufferPoolAcquireParams
s ((Ptr BufferPoolAcquireParams -> IO Int64) -> IO Int64)
-> (Ptr BufferPoolAcquireParams -> IO Int64) -> IO Int64
forall a b. (a -> b) -> a -> b
$ \Ptr BufferPoolAcquireParams
ptr -> do
Int64
val <- Ptr Int64 -> IO Int64
forall a. Storable a => Ptr a -> IO a
peek (Ptr BufferPoolAcquireParams
ptr Ptr BufferPoolAcquireParams -> Int -> Ptr Int64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) :: IO Int64
Int64 -> IO Int64
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int64
val
setBufferPoolAcquireParamsStart :: MonadIO m => BufferPoolAcquireParams -> Int64 -> m ()
setBufferPoolAcquireParamsStart :: forall (m :: * -> *).
MonadIO m =>
BufferPoolAcquireParams -> Int64 -> m ()
setBufferPoolAcquireParamsStart BufferPoolAcquireParams
s Int64
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ BufferPoolAcquireParams
-> (Ptr BufferPoolAcquireParams -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr BufferPoolAcquireParams
s ((Ptr BufferPoolAcquireParams -> IO ()) -> IO ())
-> (Ptr BufferPoolAcquireParams -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr BufferPoolAcquireParams
ptr -> do
Ptr Int64 -> Int64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr BufferPoolAcquireParams
ptr Ptr BufferPoolAcquireParams -> Int -> Ptr Int64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (Int64
val :: Int64)
#if defined(ENABLE_OVERLOADING)
data BufferPoolAcquireParamsStartFieldInfo
instance AttrInfo BufferPoolAcquireParamsStartFieldInfo where
type AttrBaseTypeConstraint BufferPoolAcquireParamsStartFieldInfo = (~) BufferPoolAcquireParams
type AttrAllowedOps BufferPoolAcquireParamsStartFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint BufferPoolAcquireParamsStartFieldInfo = (~) Int64
type AttrTransferTypeConstraint BufferPoolAcquireParamsStartFieldInfo = (~)Int64
type AttrTransferType BufferPoolAcquireParamsStartFieldInfo = Int64
type AttrGetType BufferPoolAcquireParamsStartFieldInfo = Int64
type AttrLabel BufferPoolAcquireParamsStartFieldInfo = "start"
type AttrOrigin BufferPoolAcquireParamsStartFieldInfo = BufferPoolAcquireParams
attrGet = getBufferPoolAcquireParamsStart
attrSet = setBufferPoolAcquireParamsStart
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gst.Structs.BufferPoolAcquireParams.start"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.26/docs/GI-Gst-Structs-BufferPoolAcquireParams.html#g:attr:start"
})
bufferPoolAcquireParams_start :: AttrLabelProxy "start"
bufferPoolAcquireParams_start = AttrLabelProxy
#endif
getBufferPoolAcquireParamsStop :: MonadIO m => BufferPoolAcquireParams -> m Int64
getBufferPoolAcquireParamsStop :: forall (m :: * -> *).
MonadIO m =>
BufferPoolAcquireParams -> m Int64
getBufferPoolAcquireParamsStop BufferPoolAcquireParams
s = IO Int64 -> m Int64
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int64 -> m Int64) -> IO Int64 -> m Int64
forall a b. (a -> b) -> a -> b
$ BufferPoolAcquireParams
-> (Ptr BufferPoolAcquireParams -> IO Int64) -> IO Int64
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr BufferPoolAcquireParams
s ((Ptr BufferPoolAcquireParams -> IO Int64) -> IO Int64)
-> (Ptr BufferPoolAcquireParams -> IO Int64) -> IO Int64
forall a b. (a -> b) -> a -> b
$ \Ptr BufferPoolAcquireParams
ptr -> do
Int64
val <- Ptr Int64 -> IO Int64
forall a. Storable a => Ptr a -> IO a
peek (Ptr BufferPoolAcquireParams
ptr Ptr BufferPoolAcquireParams -> Int -> Ptr Int64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) :: IO Int64
Int64 -> IO Int64
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int64
val
setBufferPoolAcquireParamsStop :: MonadIO m => BufferPoolAcquireParams -> Int64 -> m ()
setBufferPoolAcquireParamsStop :: forall (m :: * -> *).
MonadIO m =>
BufferPoolAcquireParams -> Int64 -> m ()
setBufferPoolAcquireParamsStop BufferPoolAcquireParams
s Int64
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ BufferPoolAcquireParams
-> (Ptr BufferPoolAcquireParams -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr BufferPoolAcquireParams
s ((Ptr BufferPoolAcquireParams -> IO ()) -> IO ())
-> (Ptr BufferPoolAcquireParams -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr BufferPoolAcquireParams
ptr -> do
Ptr Int64 -> Int64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr BufferPoolAcquireParams
ptr Ptr BufferPoolAcquireParams -> Int -> Ptr Int64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (Int64
val :: Int64)
#if defined(ENABLE_OVERLOADING)
data BufferPoolAcquireParamsStopFieldInfo
instance AttrInfo BufferPoolAcquireParamsStopFieldInfo where
type AttrBaseTypeConstraint BufferPoolAcquireParamsStopFieldInfo = (~) BufferPoolAcquireParams
type AttrAllowedOps BufferPoolAcquireParamsStopFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint BufferPoolAcquireParamsStopFieldInfo = (~) Int64
type AttrTransferTypeConstraint BufferPoolAcquireParamsStopFieldInfo = (~)Int64
type AttrTransferType BufferPoolAcquireParamsStopFieldInfo = Int64
type AttrGetType BufferPoolAcquireParamsStopFieldInfo = Int64
type AttrLabel BufferPoolAcquireParamsStopFieldInfo = "stop"
type AttrOrigin BufferPoolAcquireParamsStopFieldInfo = BufferPoolAcquireParams
attrGet = getBufferPoolAcquireParamsStop
attrSet = setBufferPoolAcquireParamsStop
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gst.Structs.BufferPoolAcquireParams.stop"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.26/docs/GI-Gst-Structs-BufferPoolAcquireParams.html#g:attr:stop"
})
bufferPoolAcquireParams_stop :: AttrLabelProxy "stop"
bufferPoolAcquireParams_stop = AttrLabelProxy
#endif
getBufferPoolAcquireParamsFlags :: MonadIO m => BufferPoolAcquireParams -> m [Gst.Flags.BufferPoolAcquireFlags]
getBufferPoolAcquireParamsFlags :: forall (m :: * -> *).
MonadIO m =>
BufferPoolAcquireParams -> m [BufferPoolAcquireFlags]
getBufferPoolAcquireParamsFlags BufferPoolAcquireParams
s = IO [BufferPoolAcquireFlags] -> m [BufferPoolAcquireFlags]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [BufferPoolAcquireFlags] -> m [BufferPoolAcquireFlags])
-> IO [BufferPoolAcquireFlags] -> m [BufferPoolAcquireFlags]
forall a b. (a -> b) -> a -> b
$ BufferPoolAcquireParams
-> (Ptr BufferPoolAcquireParams -> IO [BufferPoolAcquireFlags])
-> IO [BufferPoolAcquireFlags]
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr BufferPoolAcquireParams
s ((Ptr BufferPoolAcquireParams -> IO [BufferPoolAcquireFlags])
-> IO [BufferPoolAcquireFlags])
-> (Ptr BufferPoolAcquireParams -> IO [BufferPoolAcquireFlags])
-> IO [BufferPoolAcquireFlags]
forall a b. (a -> b) -> a -> b
$ \Ptr BufferPoolAcquireParams
ptr -> do
CUInt
val <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr BufferPoolAcquireParams
ptr Ptr BufferPoolAcquireParams -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) :: IO CUInt
let val' :: [BufferPoolAcquireFlags]
val' = CUInt -> [BufferPoolAcquireFlags]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
val
[BufferPoolAcquireFlags] -> IO [BufferPoolAcquireFlags]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [BufferPoolAcquireFlags]
val'
setBufferPoolAcquireParamsFlags :: MonadIO m => BufferPoolAcquireParams -> [Gst.Flags.BufferPoolAcquireFlags] -> m ()
setBufferPoolAcquireParamsFlags :: forall (m :: * -> *).
MonadIO m =>
BufferPoolAcquireParams -> [BufferPoolAcquireFlags] -> m ()
setBufferPoolAcquireParamsFlags BufferPoolAcquireParams
s [BufferPoolAcquireFlags]
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ BufferPoolAcquireParams
-> (Ptr BufferPoolAcquireParams -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr BufferPoolAcquireParams
s ((Ptr BufferPoolAcquireParams -> IO ()) -> IO ())
-> (Ptr BufferPoolAcquireParams -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr BufferPoolAcquireParams
ptr -> do
let val' :: CUInt
val' = [BufferPoolAcquireFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [BufferPoolAcquireFlags]
val
Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr BufferPoolAcquireParams
ptr Ptr BufferPoolAcquireParams -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) (CUInt
val' :: CUInt)
#if defined(ENABLE_OVERLOADING)
data BufferPoolAcquireParamsFlagsFieldInfo
instance AttrInfo BufferPoolAcquireParamsFlagsFieldInfo where
type AttrBaseTypeConstraint BufferPoolAcquireParamsFlagsFieldInfo = (~) BufferPoolAcquireParams
type AttrAllowedOps BufferPoolAcquireParamsFlagsFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint BufferPoolAcquireParamsFlagsFieldInfo = (~) [Gst.Flags.BufferPoolAcquireFlags]
type AttrTransferTypeConstraint BufferPoolAcquireParamsFlagsFieldInfo = (~)[Gst.Flags.BufferPoolAcquireFlags]
type AttrTransferType BufferPoolAcquireParamsFlagsFieldInfo = [Gst.Flags.BufferPoolAcquireFlags]
type AttrGetType BufferPoolAcquireParamsFlagsFieldInfo = [Gst.Flags.BufferPoolAcquireFlags]
type AttrLabel BufferPoolAcquireParamsFlagsFieldInfo = "flags"
type AttrOrigin BufferPoolAcquireParamsFlagsFieldInfo = BufferPoolAcquireParams
attrGet = getBufferPoolAcquireParamsFlags
attrSet = setBufferPoolAcquireParamsFlags
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gst.Structs.BufferPoolAcquireParams.flags"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.26/docs/GI-Gst-Structs-BufferPoolAcquireParams.html#g:attr:flags"
})
bufferPoolAcquireParams_flags :: AttrLabelProxy "flags"
bufferPoolAcquireParams_flags = AttrLabelProxy
#endif
#if defined(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 defined(ENABLE_OVERLOADING)
type family ResolveBufferPoolAcquireParamsMethod (t :: Symbol) (o :: *) :: * where
ResolveBufferPoolAcquireParamsMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveBufferPoolAcquireParamsMethod t BufferPoolAcquireParams, O.OverloadedMethod info BufferPoolAcquireParams p) => OL.IsLabel t (BufferPoolAcquireParams -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveBufferPoolAcquireParamsMethod t BufferPoolAcquireParams, O.OverloadedMethod info BufferPoolAcquireParams p, R.HasField t BufferPoolAcquireParams p) => R.HasField t BufferPoolAcquireParams p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveBufferPoolAcquireParamsMethod t BufferPoolAcquireParams, O.OverloadedMethodInfo info BufferPoolAcquireParams) => OL.IsLabel t (O.MethodProxy info BufferPoolAcquireParams) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif