{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gst.Structs.AllocationParams
(
AllocationParams(..) ,
newZeroAllocationParams ,
#if defined(ENABLE_OVERLOADING)
ResolveAllocationParamsMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
AllocationParamsCopyMethodInfo ,
#endif
allocationParamsCopy ,
#if defined(ENABLE_OVERLOADING)
AllocationParamsFreeMethodInfo ,
#endif
allocationParamsFree ,
#if defined(ENABLE_OVERLOADING)
AllocationParamsInitMethodInfo ,
#endif
allocationParamsInit ,
allocationParamsNew ,
#if defined(ENABLE_OVERLOADING)
allocationParams_align ,
#endif
getAllocationParamsAlign ,
setAllocationParamsAlign ,
#if defined(ENABLE_OVERLOADING)
allocationParams_flags ,
#endif
getAllocationParamsFlags ,
setAllocationParamsFlags ,
#if defined(ENABLE_OVERLOADING)
allocationParams_padding ,
#endif
getAllocationParamsPadding ,
setAllocationParamsPadding ,
#if defined(ENABLE_OVERLOADING)
allocationParams_prefix ,
#endif
getAllocationParamsPrefix ,
setAllocationParamsPrefix ,
) 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.Kind as DK
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 qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
import {-# SOURCE #-} qualified GI.Gst.Flags as Gst.Flags
#else
import {-# SOURCE #-} qualified GI.Gst.Flags as Gst.Flags
#endif
newtype AllocationParams = AllocationParams (SP.ManagedPtr AllocationParams)
deriving (AllocationParams -> AllocationParams -> Bool
(AllocationParams -> AllocationParams -> Bool)
-> (AllocationParams -> AllocationParams -> Bool)
-> Eq AllocationParams
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AllocationParams -> AllocationParams -> Bool
== :: AllocationParams -> AllocationParams -> Bool
$c/= :: AllocationParams -> AllocationParams -> Bool
/= :: AllocationParams -> AllocationParams -> Bool
Eq)
instance SP.ManagedPtrNewtype AllocationParams where
toManagedPtr :: AllocationParams -> ManagedPtr AllocationParams
toManagedPtr (AllocationParams ManagedPtr AllocationParams
p) = ManagedPtr AllocationParams
p
foreign import ccall "gst_allocation_params_get_type" c_gst_allocation_params_get_type ::
IO GType
type instance O.ParentTypes AllocationParams = '[]
instance O.HasParentTypes AllocationParams
instance B.Types.TypedObject AllocationParams where
glibType :: IO GType
glibType = IO GType
c_gst_allocation_params_get_type
instance B.Types.GBoxed AllocationParams
instance B.GValue.IsGValue (Maybe AllocationParams) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gst_allocation_params_get_type
gvalueSet_ :: Ptr GValue -> Maybe AllocationParams -> IO ()
gvalueSet_ Ptr GValue
gv Maybe AllocationParams
P.Nothing = Ptr GValue -> Ptr AllocationParams -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr AllocationParams
forall a. Ptr a
FP.nullPtr :: FP.Ptr AllocationParams)
gvalueSet_ Ptr GValue
gv (P.Just AllocationParams
obj) = AllocationParams -> (Ptr AllocationParams -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr AllocationParams
obj (Ptr GValue -> Ptr AllocationParams -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe AllocationParams)
gvalueGet_ Ptr GValue
gv = do
Ptr AllocationParams
ptr <- Ptr GValue -> IO (Ptr AllocationParams)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr AllocationParams)
if Ptr AllocationParams
ptr Ptr AllocationParams -> Ptr AllocationParams -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr AllocationParams
forall a. Ptr a
FP.nullPtr
then AllocationParams -> Maybe AllocationParams
forall a. a -> Maybe a
P.Just (AllocationParams -> Maybe AllocationParams)
-> IO AllocationParams -> IO (Maybe AllocationParams)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr AllocationParams -> AllocationParams)
-> Ptr AllocationParams -> IO AllocationParams
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr AllocationParams -> AllocationParams
AllocationParams Ptr AllocationParams
ptr
else Maybe AllocationParams -> IO (Maybe AllocationParams)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe AllocationParams
forall a. Maybe a
P.Nothing
newZeroAllocationParams :: MonadIO m => m AllocationParams
newZeroAllocationParams :: forall (m :: * -> *). MonadIO m => m AllocationParams
newZeroAllocationParams = IO AllocationParams -> m AllocationParams
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AllocationParams -> m AllocationParams)
-> IO AllocationParams -> m AllocationParams
forall a b. (a -> b) -> a -> b
$ Int -> IO (Ptr AllocationParams)
forall a. GBoxed a => Int -> IO (Ptr a)
callocBoxedBytes Int
64 IO (Ptr AllocationParams)
-> (Ptr AllocationParams -> IO AllocationParams)
-> IO AllocationParams
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr AllocationParams -> AllocationParams)
-> Ptr AllocationParams -> IO AllocationParams
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr AllocationParams -> AllocationParams
AllocationParams
instance tag ~ 'AttrSet => Constructible AllocationParams tag where
new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr AllocationParams -> AllocationParams)
-> [AttrOp AllocationParams tag] -> m AllocationParams
new ManagedPtr AllocationParams -> AllocationParams
_ [AttrOp AllocationParams tag]
attrs = do
AllocationParams
o <- m AllocationParams
forall (m :: * -> *). MonadIO m => m AllocationParams
newZeroAllocationParams
AllocationParams -> [AttrOp AllocationParams 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set AllocationParams
o [AttrOp AllocationParams tag]
[AttrOp AllocationParams 'AttrSet]
attrs
AllocationParams -> m AllocationParams
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return AllocationParams
o
getAllocationParamsFlags :: MonadIO m => AllocationParams -> m [Gst.Flags.MemoryFlags]
getAllocationParamsFlags :: forall (m :: * -> *).
MonadIO m =>
AllocationParams -> m [MemoryFlags]
getAllocationParamsFlags AllocationParams
s = IO [MemoryFlags] -> m [MemoryFlags]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [MemoryFlags] -> m [MemoryFlags])
-> IO [MemoryFlags] -> m [MemoryFlags]
forall a b. (a -> b) -> a -> b
$ AllocationParams
-> (Ptr AllocationParams -> IO [MemoryFlags]) -> IO [MemoryFlags]
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr AllocationParams
s ((Ptr AllocationParams -> IO [MemoryFlags]) -> IO [MemoryFlags])
-> (Ptr AllocationParams -> IO [MemoryFlags]) -> IO [MemoryFlags]
forall a b. (a -> b) -> a -> b
$ \Ptr AllocationParams
ptr -> do
CUInt
val <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr AllocationParams
ptr Ptr AllocationParams -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO CUInt
let val' :: [MemoryFlags]
val' = CUInt -> [MemoryFlags]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
val
[MemoryFlags] -> IO [MemoryFlags]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [MemoryFlags]
val'
setAllocationParamsFlags :: MonadIO m => AllocationParams -> [Gst.Flags.MemoryFlags] -> m ()
setAllocationParamsFlags :: forall (m :: * -> *).
MonadIO m =>
AllocationParams -> [MemoryFlags] -> m ()
setAllocationParamsFlags AllocationParams
s [MemoryFlags]
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
$ AllocationParams -> (Ptr AllocationParams -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr AllocationParams
s ((Ptr AllocationParams -> IO ()) -> IO ())
-> (Ptr AllocationParams -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr AllocationParams
ptr -> do
let val' :: CUInt
val' = [MemoryFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [MemoryFlags]
val
Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr AllocationParams
ptr Ptr AllocationParams -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (CUInt
val' :: CUInt)
#if defined(ENABLE_OVERLOADING)
data AllocationParamsFlagsFieldInfo
instance AttrInfo AllocationParamsFlagsFieldInfo where
type AttrBaseTypeConstraint AllocationParamsFlagsFieldInfo = (~) AllocationParams
type AttrAllowedOps AllocationParamsFlagsFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint AllocationParamsFlagsFieldInfo = (~) [Gst.Flags.MemoryFlags]
type AttrTransferTypeConstraint AllocationParamsFlagsFieldInfo = (~)[Gst.Flags.MemoryFlags]
type AttrTransferType AllocationParamsFlagsFieldInfo = [Gst.Flags.MemoryFlags]
type AttrGetType AllocationParamsFlagsFieldInfo = [Gst.Flags.MemoryFlags]
type AttrLabel AllocationParamsFlagsFieldInfo = "flags"
type AttrOrigin AllocationParamsFlagsFieldInfo = AllocationParams
attrGet = getAllocationParamsFlags
attrSet = setAllocationParamsFlags
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gst.Structs.AllocationParams.flags"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.30/docs/GI-Gst-Structs-AllocationParams.html#g:attr:flags"
})
allocationParams_flags :: AttrLabelProxy "flags"
allocationParams_flags = AttrLabelProxy
#endif
getAllocationParamsAlign :: MonadIO m => AllocationParams -> m FCT.CSize
getAllocationParamsAlign :: forall (m :: * -> *). MonadIO m => AllocationParams -> m CSize
getAllocationParamsAlign AllocationParams
s = IO CSize -> m CSize
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CSize -> m CSize) -> IO CSize -> m CSize
forall a b. (a -> b) -> a -> b
$ AllocationParams -> (Ptr AllocationParams -> IO CSize) -> IO CSize
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr AllocationParams
s ((Ptr AllocationParams -> IO CSize) -> IO CSize)
-> (Ptr AllocationParams -> IO CSize) -> IO CSize
forall a b. (a -> b) -> a -> b
$ \Ptr AllocationParams
ptr -> do
CSize
val <- Ptr CSize -> IO CSize
forall a. Storable a => Ptr a -> IO a
peek (Ptr AllocationParams
ptr Ptr AllocationParams -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) :: IO FCT.CSize
CSize -> IO CSize
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CSize
val
setAllocationParamsAlign :: MonadIO m => AllocationParams -> FCT.CSize -> m ()
setAllocationParamsAlign :: forall (m :: * -> *).
MonadIO m =>
AllocationParams -> CSize -> m ()
setAllocationParamsAlign AllocationParams
s CSize
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
$ AllocationParams -> (Ptr AllocationParams -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr AllocationParams
s ((Ptr AllocationParams -> IO ()) -> IO ())
-> (Ptr AllocationParams -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr AllocationParams
ptr -> do
Ptr CSize -> CSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr AllocationParams
ptr Ptr AllocationParams -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (CSize
val :: FCT.CSize)
#if defined(ENABLE_OVERLOADING)
data AllocationParamsAlignFieldInfo
instance AttrInfo AllocationParamsAlignFieldInfo where
type AttrBaseTypeConstraint AllocationParamsAlignFieldInfo = (~) AllocationParams
type AttrAllowedOps AllocationParamsAlignFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint AllocationParamsAlignFieldInfo = (~) FCT.CSize
type AttrTransferTypeConstraint AllocationParamsAlignFieldInfo = (~)FCT.CSize
type AttrTransferType AllocationParamsAlignFieldInfo = FCT.CSize
type AttrGetType AllocationParamsAlignFieldInfo = FCT.CSize
type AttrLabel AllocationParamsAlignFieldInfo = "align"
type AttrOrigin AllocationParamsAlignFieldInfo = AllocationParams
attrGet = getAllocationParamsAlign
attrSet = setAllocationParamsAlign
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gst.Structs.AllocationParams.align"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.30/docs/GI-Gst-Structs-AllocationParams.html#g:attr:align"
})
allocationParams_align :: AttrLabelProxy "align"
allocationParams_align = AttrLabelProxy
#endif
getAllocationParamsPrefix :: MonadIO m => AllocationParams -> m FCT.CSize
getAllocationParamsPrefix :: forall (m :: * -> *). MonadIO m => AllocationParams -> m CSize
getAllocationParamsPrefix AllocationParams
s = IO CSize -> m CSize
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CSize -> m CSize) -> IO CSize -> m CSize
forall a b. (a -> b) -> a -> b
$ AllocationParams -> (Ptr AllocationParams -> IO CSize) -> IO CSize
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr AllocationParams
s ((Ptr AllocationParams -> IO CSize) -> IO CSize)
-> (Ptr AllocationParams -> IO CSize) -> IO CSize
forall a b. (a -> b) -> a -> b
$ \Ptr AllocationParams
ptr -> do
CSize
val <- Ptr CSize -> IO CSize
forall a. Storable a => Ptr a -> IO a
peek (Ptr AllocationParams
ptr Ptr AllocationParams -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) :: IO FCT.CSize
CSize -> IO CSize
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CSize
val
setAllocationParamsPrefix :: MonadIO m => AllocationParams -> FCT.CSize -> m ()
setAllocationParamsPrefix :: forall (m :: * -> *).
MonadIO m =>
AllocationParams -> CSize -> m ()
setAllocationParamsPrefix AllocationParams
s CSize
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
$ AllocationParams -> (Ptr AllocationParams -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr AllocationParams
s ((Ptr AllocationParams -> IO ()) -> IO ())
-> (Ptr AllocationParams -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr AllocationParams
ptr -> do
Ptr CSize -> CSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr AllocationParams
ptr Ptr AllocationParams -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (CSize
val :: FCT.CSize)
#if defined(ENABLE_OVERLOADING)
data AllocationParamsPrefixFieldInfo
instance AttrInfo AllocationParamsPrefixFieldInfo where
type AttrBaseTypeConstraint AllocationParamsPrefixFieldInfo = (~) AllocationParams
type AttrAllowedOps AllocationParamsPrefixFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint AllocationParamsPrefixFieldInfo = (~) FCT.CSize
type AttrTransferTypeConstraint AllocationParamsPrefixFieldInfo = (~)FCT.CSize
type AttrTransferType AllocationParamsPrefixFieldInfo = FCT.CSize
type AttrGetType AllocationParamsPrefixFieldInfo = FCT.CSize
type AttrLabel AllocationParamsPrefixFieldInfo = "prefix"
type AttrOrigin AllocationParamsPrefixFieldInfo = AllocationParams
attrGet = getAllocationParamsPrefix
attrSet = setAllocationParamsPrefix
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gst.Structs.AllocationParams.prefix"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.30/docs/GI-Gst-Structs-AllocationParams.html#g:attr:prefix"
})
allocationParams_prefix :: AttrLabelProxy "prefix"
allocationParams_prefix = AttrLabelProxy
#endif
getAllocationParamsPadding :: MonadIO m => AllocationParams -> m FCT.CSize
getAllocationParamsPadding :: forall (m :: * -> *). MonadIO m => AllocationParams -> m CSize
getAllocationParamsPadding AllocationParams
s = IO CSize -> m CSize
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CSize -> m CSize) -> IO CSize -> m CSize
forall a b. (a -> b) -> a -> b
$ AllocationParams -> (Ptr AllocationParams -> IO CSize) -> IO CSize
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr AllocationParams
s ((Ptr AllocationParams -> IO CSize) -> IO CSize)
-> (Ptr AllocationParams -> IO CSize) -> IO CSize
forall a b. (a -> b) -> a -> b
$ \Ptr AllocationParams
ptr -> do
CSize
val <- Ptr CSize -> IO CSize
forall a. Storable a => Ptr a -> IO a
peek (Ptr AllocationParams
ptr Ptr AllocationParams -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) :: IO FCT.CSize
CSize -> IO CSize
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CSize
val
setAllocationParamsPadding :: MonadIO m => AllocationParams -> FCT.CSize -> m ()
setAllocationParamsPadding :: forall (m :: * -> *).
MonadIO m =>
AllocationParams -> CSize -> m ()
setAllocationParamsPadding AllocationParams
s CSize
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
$ AllocationParams -> (Ptr AllocationParams -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr AllocationParams
s ((Ptr AllocationParams -> IO ()) -> IO ())
-> (Ptr AllocationParams -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr AllocationParams
ptr -> do
Ptr CSize -> CSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr AllocationParams
ptr Ptr AllocationParams -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) (CSize
val :: FCT.CSize)
#if defined(ENABLE_OVERLOADING)
data AllocationParamsPaddingFieldInfo
instance AttrInfo AllocationParamsPaddingFieldInfo where
type AttrBaseTypeConstraint AllocationParamsPaddingFieldInfo = (~) AllocationParams
type AttrAllowedOps AllocationParamsPaddingFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint AllocationParamsPaddingFieldInfo = (~) FCT.CSize
type AttrTransferTypeConstraint AllocationParamsPaddingFieldInfo = (~)FCT.CSize
type AttrTransferType AllocationParamsPaddingFieldInfo = FCT.CSize
type AttrGetType AllocationParamsPaddingFieldInfo = FCT.CSize
type AttrLabel AllocationParamsPaddingFieldInfo = "padding"
type AttrOrigin AllocationParamsPaddingFieldInfo = AllocationParams
attrGet = getAllocationParamsPadding
attrSet = setAllocationParamsPadding
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gst.Structs.AllocationParams.padding"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.30/docs/GI-Gst-Structs-AllocationParams.html#g:attr:padding"
})
allocationParams_padding :: AttrLabelProxy "padding"
allocationParams_padding = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList AllocationParams
type instance O.AttributeList AllocationParams = AllocationParamsAttributeList
type AllocationParamsAttributeList = ('[ '("flags", AllocationParamsFlagsFieldInfo), '("align", AllocationParamsAlignFieldInfo), '("prefix", AllocationParamsPrefixFieldInfo), '("padding", AllocationParamsPaddingFieldInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "gst_allocation_params_new" gst_allocation_params_new ::
IO (Ptr AllocationParams)
allocationParamsNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
m AllocationParams
allocationParamsNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
m AllocationParams
allocationParamsNew = IO AllocationParams -> m AllocationParams
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AllocationParams -> m AllocationParams)
-> IO AllocationParams -> m AllocationParams
forall a b. (a -> b) -> a -> b
$ do
Ptr AllocationParams
result <- IO (Ptr AllocationParams)
gst_allocation_params_new
Text -> Ptr AllocationParams -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"allocationParamsNew" Ptr AllocationParams
result
AllocationParams
result' <- ((ManagedPtr AllocationParams -> AllocationParams)
-> Ptr AllocationParams -> IO AllocationParams
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr AllocationParams -> AllocationParams
AllocationParams) Ptr AllocationParams
result
AllocationParams -> IO AllocationParams
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return AllocationParams
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gst_allocation_params_copy" gst_allocation_params_copy ::
Ptr AllocationParams ->
IO (Ptr AllocationParams)
allocationParamsCopy ::
(B.CallStack.HasCallStack, MonadIO m) =>
Maybe (AllocationParams)
-> m (Maybe AllocationParams)
allocationParamsCopy :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Maybe AllocationParams -> m (Maybe AllocationParams)
allocationParamsCopy Maybe AllocationParams
params = IO (Maybe AllocationParams) -> m (Maybe AllocationParams)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe AllocationParams) -> m (Maybe AllocationParams))
-> IO (Maybe AllocationParams) -> m (Maybe AllocationParams)
forall a b. (a -> b) -> a -> b
$ do
Ptr AllocationParams
maybeParams <- case Maybe AllocationParams
params of
Maybe AllocationParams
Nothing -> Ptr AllocationParams -> IO (Ptr AllocationParams)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr AllocationParams
forall a. Ptr a
nullPtr
Just AllocationParams
jParams -> do
Ptr AllocationParams
jParams' <- AllocationParams -> IO (Ptr AllocationParams)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AllocationParams
jParams
Ptr AllocationParams -> IO (Ptr AllocationParams)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr AllocationParams
jParams'
Ptr AllocationParams
result <- Ptr AllocationParams -> IO (Ptr AllocationParams)
gst_allocation_params_copy Ptr AllocationParams
maybeParams
Maybe AllocationParams
maybeResult <- Ptr AllocationParams
-> (Ptr AllocationParams -> IO AllocationParams)
-> IO (Maybe AllocationParams)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr AllocationParams
result ((Ptr AllocationParams -> IO AllocationParams)
-> IO (Maybe AllocationParams))
-> (Ptr AllocationParams -> IO AllocationParams)
-> IO (Maybe AllocationParams)
forall a b. (a -> b) -> a -> b
$ \Ptr AllocationParams
result' -> do
AllocationParams
result'' <- ((ManagedPtr AllocationParams -> AllocationParams)
-> Ptr AllocationParams -> IO AllocationParams
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr AllocationParams -> AllocationParams
AllocationParams) Ptr AllocationParams
result'
AllocationParams -> IO AllocationParams
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return AllocationParams
result''
Maybe AllocationParams -> (AllocationParams -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe AllocationParams
params AllocationParams -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Maybe AllocationParams -> IO (Maybe AllocationParams)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe AllocationParams
maybeResult
#if defined(ENABLE_OVERLOADING)
data AllocationParamsCopyMethodInfo
instance (signature ~ (m (Maybe AllocationParams)), MonadIO m) => O.OverloadedMethod AllocationParamsCopyMethodInfo AllocationParams signature where
overloadedMethod i = allocationParamsCopy (Just i)
instance O.OverloadedMethodInfo AllocationParamsCopyMethodInfo AllocationParams where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gst.Structs.AllocationParams.allocationParamsCopy",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.30/docs/GI-Gst-Structs-AllocationParams.html#v:allocationParamsCopy"
})
#endif
foreign import ccall "gst_allocation_params_free" gst_allocation_params_free ::
Ptr AllocationParams ->
IO ()
allocationParamsFree ::
(B.CallStack.HasCallStack, MonadIO m) =>
AllocationParams
-> m ()
allocationParamsFree :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AllocationParams -> m ()
allocationParamsFree AllocationParams
params = 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
$ do
Ptr AllocationParams
params' <- AllocationParams -> IO (Ptr AllocationParams)
forall a. (HasCallStack, GBoxed a) => a -> IO (Ptr a)
B.ManagedPtr.disownBoxed AllocationParams
params
Ptr AllocationParams -> IO ()
gst_allocation_params_free Ptr AllocationParams
params'
AllocationParams -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AllocationParams
params
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data AllocationParamsFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod AllocationParamsFreeMethodInfo AllocationParams signature where
overloadedMethod = allocationParamsFree
instance O.OverloadedMethodInfo AllocationParamsFreeMethodInfo AllocationParams where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gst.Structs.AllocationParams.allocationParamsFree",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.30/docs/GI-Gst-Structs-AllocationParams.html#v:allocationParamsFree"
})
#endif
foreign import ccall "gst_allocation_params_init" gst_allocation_params_init ::
Ptr AllocationParams ->
IO ()
allocationParamsInit ::
(B.CallStack.HasCallStack, MonadIO m) =>
AllocationParams
-> m ()
allocationParamsInit :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AllocationParams -> m ()
allocationParamsInit AllocationParams
params = 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
$ do
Ptr AllocationParams
params' <- AllocationParams -> IO (Ptr AllocationParams)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AllocationParams
params
Ptr AllocationParams -> IO ()
gst_allocation_params_init Ptr AllocationParams
params'
AllocationParams -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AllocationParams
params
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data AllocationParamsInitMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod AllocationParamsInitMethodInfo AllocationParams signature where
overloadedMethod = allocationParamsInit
instance O.OverloadedMethodInfo AllocationParamsInitMethodInfo AllocationParams where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gst.Structs.AllocationParams.allocationParamsInit",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gst-1.0.30/docs/GI-Gst-Structs-AllocationParams.html#v:allocationParamsInit"
})
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveAllocationParamsMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveAllocationParamsMethod "copy" o = AllocationParamsCopyMethodInfo
ResolveAllocationParamsMethod "free" o = AllocationParamsFreeMethodInfo
ResolveAllocationParamsMethod "init" o = AllocationParamsInitMethodInfo
ResolveAllocationParamsMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveAllocationParamsMethod t AllocationParams, O.OverloadedMethod info AllocationParams p) => OL.IsLabel t (AllocationParams -> 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 ~ ResolveAllocationParamsMethod t AllocationParams, O.OverloadedMethod info AllocationParams p, R.HasField t AllocationParams p) => R.HasField t AllocationParams p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveAllocationParamsMethod t AllocationParams, O.OverloadedMethodInfo info AllocationParams) => OL.IsLabel t (O.MethodProxy info AllocationParams) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif