{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gst.Structs.Memory
(
Memory(..) ,
newZeroMemory ,
noMemory ,
#if defined(ENABLE_OVERLOADING)
ResolveMemoryMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
MemoryCopyMethodInfo ,
#endif
memoryCopy ,
#if defined(ENABLE_OVERLOADING)
MemoryGetSizesMethodInfo ,
#endif
memoryGetSizes ,
#if defined(ENABLE_OVERLOADING)
MemoryIsSpanMethodInfo ,
#endif
memoryIsSpan ,
#if defined(ENABLE_OVERLOADING)
MemoryIsTypeMethodInfo ,
#endif
memoryIsType ,
#if defined(ENABLE_OVERLOADING)
MemoryMakeMappedMethodInfo ,
#endif
memoryMakeMapped ,
#if defined(ENABLE_OVERLOADING)
MemoryMapMethodInfo ,
#endif
memoryMap ,
memoryNewWrapped ,
#if defined(ENABLE_OVERLOADING)
MemoryResizeMethodInfo ,
#endif
memoryResize ,
#if defined(ENABLE_OVERLOADING)
MemoryShareMethodInfo ,
#endif
memoryShare ,
#if defined(ENABLE_OVERLOADING)
MemoryUnmapMethodInfo ,
#endif
memoryUnmap ,
getMemoryAlign ,
#if defined(ENABLE_OVERLOADING)
memory_align ,
#endif
setMemoryAlign ,
clearMemoryAllocator ,
getMemoryAllocator ,
#if defined(ENABLE_OVERLOADING)
memory_allocator ,
#endif
setMemoryAllocator ,
getMemoryMaxsize ,
#if defined(ENABLE_OVERLOADING)
memory_maxsize ,
#endif
setMemoryMaxsize ,
getMemoryMiniObject ,
#if defined(ENABLE_OVERLOADING)
memory_miniObject ,
#endif
getMemoryOffset ,
#if defined(ENABLE_OVERLOADING)
memory_offset ,
#endif
setMemoryOffset ,
clearMemoryParent ,
getMemoryParent ,
#if defined(ENABLE_OVERLOADING)
memory_parent ,
#endif
setMemoryParent ,
getMemorySize ,
#if defined(ENABLE_OVERLOADING)
memory_size ,
#endif
setMemorySize ,
) 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.GI.Base.Signals as B.Signals
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.GLib.Callbacks as GLib.Callbacks
import {-# SOURCE #-} qualified GI.Gst.Flags as Gst.Flags
import {-# SOURCE #-} qualified GI.Gst.Objects.Allocator as Gst.Allocator
import {-# SOURCE #-} qualified GI.Gst.Structs.MapInfo as Gst.MapInfo
import {-# SOURCE #-} qualified GI.Gst.Structs.MiniObject as Gst.MiniObject
newtype Memory = Memory (ManagedPtr Memory)
deriving (Memory -> Memory -> Bool
(Memory -> Memory -> Bool)
-> (Memory -> Memory -> Bool) -> Eq Memory
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Memory -> Memory -> Bool
$c/= :: Memory -> Memory -> Bool
== :: Memory -> Memory -> Bool
$c== :: Memory -> Memory -> Bool
Eq)
foreign import ccall "gst_memory_get_type" c_gst_memory_get_type ::
IO GType
instance BoxedObject Memory where
boxedType :: Memory -> IO GType
boxedType _ = IO GType
c_gst_memory_get_type
instance B.GValue.IsGValue Memory where
toGValue :: Memory -> IO GValue
toGValue o :: Memory
o = do
GType
gtype <- IO GType
c_gst_memory_get_type
Memory -> (Ptr Memory -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Memory
o (GType -> (GValue -> Ptr Memory -> IO ()) -> Ptr Memory -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr Memory -> IO ()
forall a. GValue -> Ptr a -> IO ()
B.GValue.set_boxed)
fromGValue :: GValue -> IO Memory
fromGValue gv :: GValue
gv = do
Ptr Memory
ptr <- GValue -> IO (Ptr Memory)
forall b. GValue -> IO (Ptr b)
B.GValue.get_boxed GValue
gv :: IO (Ptr Memory)
(ManagedPtr Memory -> Memory) -> Ptr Memory -> IO Memory
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr Memory -> Memory
Memory Ptr Memory
ptr
newZeroMemory :: MonadIO m => m Memory
newZeroMemory :: m Memory
newZeroMemory = IO Memory -> m Memory
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Memory -> m Memory) -> IO Memory -> m Memory
forall a b. (a -> b) -> a -> b
$ Int -> IO (Ptr Memory)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 112 IO (Ptr Memory) -> (Ptr Memory -> IO Memory) -> IO Memory
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr Memory -> Memory) -> Ptr Memory -> IO Memory
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Memory -> Memory
Memory
instance tag ~ 'AttrSet => Constructible Memory tag where
new :: (ManagedPtr Memory -> Memory) -> [AttrOp Memory tag] -> m Memory
new _ attrs :: [AttrOp Memory tag]
attrs = do
Memory
o <- m Memory
forall (m :: * -> *). MonadIO m => m Memory
newZeroMemory
Memory -> [AttrOp Memory 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set Memory
o [AttrOp Memory tag]
[AttrOp Memory 'AttrSet]
attrs
Memory -> m Memory
forall (m :: * -> *) a. Monad m => a -> m a
return Memory
o
noMemory :: Maybe Memory
noMemory :: Maybe Memory
noMemory = Maybe Memory
forall a. Maybe a
Nothing
getMemoryMiniObject :: MonadIO m => Memory -> m Gst.MiniObject.MiniObject
getMemoryMiniObject :: Memory -> m MiniObject
getMemoryMiniObject s :: Memory
s = IO MiniObject -> m MiniObject
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO MiniObject -> m MiniObject) -> IO MiniObject -> m MiniObject
forall a b. (a -> b) -> a -> b
$ Memory -> (Ptr Memory -> IO MiniObject) -> IO MiniObject
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Memory
s ((Ptr Memory -> IO MiniObject) -> IO MiniObject)
-> (Ptr Memory -> IO MiniObject) -> IO MiniObject
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Memory
ptr -> do
let val :: Ptr MiniObject
val = Ptr Memory
ptr Ptr Memory -> Int -> Ptr MiniObject
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: (Ptr Gst.MiniObject.MiniObject)
MiniObject
val' <- ((ManagedPtr MiniObject -> MiniObject)
-> Ptr MiniObject -> IO MiniObject
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr MiniObject -> MiniObject
Gst.MiniObject.MiniObject) Ptr MiniObject
val
MiniObject -> IO MiniObject
forall (m :: * -> *) a. Monad m => a -> m a
return MiniObject
val'
#if defined(ENABLE_OVERLOADING)
data MemoryMiniObjectFieldInfo
instance AttrInfo MemoryMiniObjectFieldInfo where
type AttrBaseTypeConstraint MemoryMiniObjectFieldInfo = (~) Memory
type AttrAllowedOps MemoryMiniObjectFieldInfo = '[ 'AttrGet]
type AttrSetTypeConstraint MemoryMiniObjectFieldInfo = (~) (Ptr Gst.MiniObject.MiniObject)
type AttrTransferTypeConstraint MemoryMiniObjectFieldInfo = (~)(Ptr Gst.MiniObject.MiniObject)
type AttrTransferType MemoryMiniObjectFieldInfo = (Ptr Gst.MiniObject.MiniObject)
type AttrGetType MemoryMiniObjectFieldInfo = Gst.MiniObject.MiniObject
type AttrLabel MemoryMiniObjectFieldInfo = "mini_object"
type AttrOrigin MemoryMiniObjectFieldInfo = Memory
attrGet = getMemoryMiniObject
attrSet = undefined
attrConstruct = undefined
attrClear = undefined
attrTransfer = undefined
memory_miniObject :: AttrLabelProxy "miniObject"
memory_miniObject = AttrLabelProxy
#endif
getMemoryAllocator :: MonadIO m => Memory -> m (Maybe Gst.Allocator.Allocator)
getMemoryAllocator :: Memory -> m (Maybe Allocator)
getMemoryAllocator s :: Memory
s = IO (Maybe Allocator) -> m (Maybe Allocator)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Allocator) -> m (Maybe Allocator))
-> IO (Maybe Allocator) -> m (Maybe Allocator)
forall a b. (a -> b) -> a -> b
$ Memory
-> (Ptr Memory -> IO (Maybe Allocator)) -> IO (Maybe Allocator)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Memory
s ((Ptr Memory -> IO (Maybe Allocator)) -> IO (Maybe Allocator))
-> (Ptr Memory -> IO (Maybe Allocator)) -> IO (Maybe Allocator)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Memory
ptr -> do
Ptr Allocator
val <- Ptr (Ptr Allocator) -> IO (Ptr Allocator)
forall a. Storable a => Ptr a -> IO a
peek (Ptr Memory
ptr Ptr Memory -> Int -> Ptr (Ptr Allocator)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64) :: IO (Ptr Gst.Allocator.Allocator)
Maybe Allocator
result <- Ptr Allocator
-> (Ptr Allocator -> IO Allocator) -> IO (Maybe Allocator)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr Allocator
val ((Ptr Allocator -> IO Allocator) -> IO (Maybe Allocator))
-> (Ptr Allocator -> IO Allocator) -> IO (Maybe Allocator)
forall a b. (a -> b) -> a -> b
$ \val' :: Ptr Allocator
val' -> do
Allocator
val'' <- ((ManagedPtr Allocator -> Allocator)
-> Ptr Allocator -> IO Allocator
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Allocator -> Allocator
Gst.Allocator.Allocator) Ptr Allocator
val'
Allocator -> IO Allocator
forall (m :: * -> *) a. Monad m => a -> m a
return Allocator
val''
Maybe Allocator -> IO (Maybe Allocator)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Allocator
result
setMemoryAllocator :: MonadIO m => Memory -> Ptr Gst.Allocator.Allocator -> m ()
setMemoryAllocator :: Memory -> Ptr Allocator -> m ()
setMemoryAllocator s :: Memory
s val :: Ptr Allocator
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Memory -> (Ptr Memory -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Memory
s ((Ptr Memory -> IO ()) -> IO ()) -> (Ptr Memory -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Memory
ptr -> do
Ptr (Ptr Allocator) -> Ptr Allocator -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Memory
ptr Ptr Memory -> Int -> Ptr (Ptr Allocator)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64) (Ptr Allocator
val :: Ptr Gst.Allocator.Allocator)
clearMemoryAllocator :: MonadIO m => Memory -> m ()
clearMemoryAllocator :: Memory -> m ()
clearMemoryAllocator s :: Memory
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Memory -> (Ptr Memory -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Memory
s ((Ptr Memory -> IO ()) -> IO ()) -> (Ptr Memory -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Memory
ptr -> do
Ptr (Ptr Allocator) -> Ptr Allocator -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Memory
ptr Ptr Memory -> Int -> Ptr (Ptr Allocator)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64) (Ptr Allocator
forall a. Ptr a
FP.nullPtr :: Ptr Gst.Allocator.Allocator)
#if defined(ENABLE_OVERLOADING)
data MemoryAllocatorFieldInfo
instance AttrInfo MemoryAllocatorFieldInfo where
type AttrBaseTypeConstraint MemoryAllocatorFieldInfo = (~) Memory
type AttrAllowedOps MemoryAllocatorFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint MemoryAllocatorFieldInfo = (~) (Ptr Gst.Allocator.Allocator)
type AttrTransferTypeConstraint MemoryAllocatorFieldInfo = (~)(Ptr Gst.Allocator.Allocator)
type AttrTransferType MemoryAllocatorFieldInfo = (Ptr Gst.Allocator.Allocator)
type AttrGetType MemoryAllocatorFieldInfo = Maybe Gst.Allocator.Allocator
type AttrLabel MemoryAllocatorFieldInfo = "allocator"
type AttrOrigin MemoryAllocatorFieldInfo = Memory
attrGet = getMemoryAllocator
attrSet = setMemoryAllocator
attrConstruct = undefined
attrClear = clearMemoryAllocator
attrTransfer _ v = do
return v
memory_allocator :: AttrLabelProxy "allocator"
memory_allocator = AttrLabelProxy
#endif
getMemoryParent :: MonadIO m => Memory -> m (Maybe Memory)
getMemoryParent :: Memory -> m (Maybe Memory)
getMemoryParent s :: Memory
s = IO (Maybe Memory) -> m (Maybe Memory)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Memory) -> m (Maybe Memory))
-> IO (Maybe Memory) -> m (Maybe Memory)
forall a b. (a -> b) -> a -> b
$ Memory -> (Ptr Memory -> IO (Maybe Memory)) -> IO (Maybe Memory)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Memory
s ((Ptr Memory -> IO (Maybe Memory)) -> IO (Maybe Memory))
-> (Ptr Memory -> IO (Maybe Memory)) -> IO (Maybe Memory)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Memory
ptr -> do
Ptr Memory
val <- Ptr (Ptr Memory) -> IO (Ptr Memory)
forall a. Storable a => Ptr a -> IO a
peek (Ptr Memory
ptr Ptr Memory -> Int -> Ptr (Ptr Memory)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72) :: IO (Ptr Memory)
Maybe Memory
result <- Ptr Memory -> (Ptr Memory -> IO Memory) -> IO (Maybe Memory)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr Memory
val ((Ptr Memory -> IO Memory) -> IO (Maybe Memory))
-> (Ptr Memory -> IO Memory) -> IO (Maybe Memory)
forall a b. (a -> b) -> a -> b
$ \val' :: Ptr Memory
val' -> do
Memory
val'' <- ((ManagedPtr Memory -> Memory) -> Ptr Memory -> IO Memory
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Memory -> Memory
Memory) Ptr Memory
val'
Memory -> IO Memory
forall (m :: * -> *) a. Monad m => a -> m a
return Memory
val''
Maybe Memory -> IO (Maybe Memory)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Memory
result
setMemoryParent :: MonadIO m => Memory -> Ptr Memory -> m ()
setMemoryParent :: Memory -> Ptr Memory -> m ()
setMemoryParent s :: Memory
s val :: Ptr Memory
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Memory -> (Ptr Memory -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Memory
s ((Ptr Memory -> IO ()) -> IO ()) -> (Ptr Memory -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Memory
ptr -> do
Ptr (Ptr Memory) -> Ptr Memory -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Memory
ptr Ptr Memory -> Int -> Ptr (Ptr Memory)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72) (Ptr Memory
val :: Ptr Memory)
clearMemoryParent :: MonadIO m => Memory -> m ()
clearMemoryParent :: Memory -> m ()
clearMemoryParent s :: Memory
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Memory -> (Ptr Memory -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Memory
s ((Ptr Memory -> IO ()) -> IO ()) -> (Ptr Memory -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Memory
ptr -> do
Ptr (Ptr Memory) -> Ptr Memory -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Memory
ptr Ptr Memory -> Int -> Ptr (Ptr Memory)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72) (Ptr Memory
forall a. Ptr a
FP.nullPtr :: Ptr Memory)
#if defined(ENABLE_OVERLOADING)
data MemoryParentFieldInfo
instance AttrInfo MemoryParentFieldInfo where
type AttrBaseTypeConstraint MemoryParentFieldInfo = (~) Memory
type AttrAllowedOps MemoryParentFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint MemoryParentFieldInfo = (~) (Ptr Memory)
type AttrTransferTypeConstraint MemoryParentFieldInfo = (~)(Ptr Memory)
type AttrTransferType MemoryParentFieldInfo = (Ptr Memory)
type AttrGetType MemoryParentFieldInfo = Maybe Memory
type AttrLabel MemoryParentFieldInfo = "parent"
type AttrOrigin MemoryParentFieldInfo = Memory
attrGet = getMemoryParent
attrSet = setMemoryParent
attrConstruct = undefined
attrClear = clearMemoryParent
attrTransfer _ v = do
return v
memory_parent :: AttrLabelProxy "parent"
memory_parent = AttrLabelProxy
#endif
getMemoryMaxsize :: MonadIO m => Memory -> m Word64
getMemoryMaxsize :: Memory -> m Word64
getMemoryMaxsize s :: Memory
s = IO Word64 -> m Word64
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word64 -> m Word64) -> IO Word64 -> m Word64
forall a b. (a -> b) -> a -> b
$ Memory -> (Ptr Memory -> IO Word64) -> IO Word64
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Memory
s ((Ptr Memory -> IO Word64) -> IO Word64)
-> (Ptr Memory -> IO Word64) -> IO Word64
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Memory
ptr -> do
Word64
val <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek (Ptr Memory
ptr Ptr Memory -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80) :: IO Word64
Word64 -> IO Word64
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
val
setMemoryMaxsize :: MonadIO m => Memory -> Word64 -> m ()
setMemoryMaxsize :: Memory -> Word64 -> m ()
setMemoryMaxsize s :: Memory
s val :: Word64
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Memory -> (Ptr Memory -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Memory
s ((Ptr Memory -> IO ()) -> IO ()) -> (Ptr Memory -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Memory
ptr -> do
Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Memory
ptr Ptr Memory -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80) (Word64
val :: Word64)
#if defined(ENABLE_OVERLOADING)
data MemoryMaxsizeFieldInfo
instance AttrInfo MemoryMaxsizeFieldInfo where
type AttrBaseTypeConstraint MemoryMaxsizeFieldInfo = (~) Memory
type AttrAllowedOps MemoryMaxsizeFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint MemoryMaxsizeFieldInfo = (~) Word64
type AttrTransferTypeConstraint MemoryMaxsizeFieldInfo = (~)Word64
type AttrTransferType MemoryMaxsizeFieldInfo = Word64
type AttrGetType MemoryMaxsizeFieldInfo = Word64
type AttrLabel MemoryMaxsizeFieldInfo = "maxsize"
type AttrOrigin MemoryMaxsizeFieldInfo = Memory
attrGet = getMemoryMaxsize
attrSet = setMemoryMaxsize
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
memory_maxsize :: AttrLabelProxy "maxsize"
memory_maxsize = AttrLabelProxy
#endif
getMemoryAlign :: MonadIO m => Memory -> m Word64
getMemoryAlign :: Memory -> m Word64
getMemoryAlign s :: Memory
s = IO Word64 -> m Word64
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word64 -> m Word64) -> IO Word64 -> m Word64
forall a b. (a -> b) -> a -> b
$ Memory -> (Ptr Memory -> IO Word64) -> IO Word64
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Memory
s ((Ptr Memory -> IO Word64) -> IO Word64)
-> (Ptr Memory -> IO Word64) -> IO Word64
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Memory
ptr -> do
Word64
val <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek (Ptr Memory
ptr Ptr Memory -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88) :: IO Word64
Word64 -> IO Word64
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
val
setMemoryAlign :: MonadIO m => Memory -> Word64 -> m ()
setMemoryAlign :: Memory -> Word64 -> m ()
setMemoryAlign s :: Memory
s val :: Word64
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Memory -> (Ptr Memory -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Memory
s ((Ptr Memory -> IO ()) -> IO ()) -> (Ptr Memory -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Memory
ptr -> do
Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Memory
ptr Ptr Memory -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88) (Word64
val :: Word64)
#if defined(ENABLE_OVERLOADING)
data MemoryAlignFieldInfo
instance AttrInfo MemoryAlignFieldInfo where
type AttrBaseTypeConstraint MemoryAlignFieldInfo = (~) Memory
type AttrAllowedOps MemoryAlignFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint MemoryAlignFieldInfo = (~) Word64
type AttrTransferTypeConstraint MemoryAlignFieldInfo = (~)Word64
type AttrTransferType MemoryAlignFieldInfo = Word64
type AttrGetType MemoryAlignFieldInfo = Word64
type AttrLabel MemoryAlignFieldInfo = "align"
type AttrOrigin MemoryAlignFieldInfo = Memory
attrGet = getMemoryAlign
attrSet = setMemoryAlign
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
memory_align :: AttrLabelProxy "align"
memory_align = AttrLabelProxy
#endif
getMemoryOffset :: MonadIO m => Memory -> m Word64
getMemoryOffset :: Memory -> m Word64
getMemoryOffset s :: Memory
s = IO Word64 -> m Word64
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word64 -> m Word64) -> IO Word64 -> m Word64
forall a b. (a -> b) -> a -> b
$ Memory -> (Ptr Memory -> IO Word64) -> IO Word64
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Memory
s ((Ptr Memory -> IO Word64) -> IO Word64)
-> (Ptr Memory -> IO Word64) -> IO Word64
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Memory
ptr -> do
Word64
val <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek (Ptr Memory
ptr Ptr Memory -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 96) :: IO Word64
Word64 -> IO Word64
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
val
setMemoryOffset :: MonadIO m => Memory -> Word64 -> m ()
setMemoryOffset :: Memory -> Word64 -> m ()
setMemoryOffset s :: Memory
s val :: Word64
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Memory -> (Ptr Memory -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Memory
s ((Ptr Memory -> IO ()) -> IO ()) -> (Ptr Memory -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Memory
ptr -> do
Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Memory
ptr Ptr Memory -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 96) (Word64
val :: Word64)
#if defined(ENABLE_OVERLOADING)
data MemoryOffsetFieldInfo
instance AttrInfo MemoryOffsetFieldInfo where
type AttrBaseTypeConstraint MemoryOffsetFieldInfo = (~) Memory
type AttrAllowedOps MemoryOffsetFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint MemoryOffsetFieldInfo = (~) Word64
type AttrTransferTypeConstraint MemoryOffsetFieldInfo = (~)Word64
type AttrTransferType MemoryOffsetFieldInfo = Word64
type AttrGetType MemoryOffsetFieldInfo = Word64
type AttrLabel MemoryOffsetFieldInfo = "offset"
type AttrOrigin MemoryOffsetFieldInfo = Memory
attrGet = getMemoryOffset
attrSet = setMemoryOffset
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
memory_offset :: AttrLabelProxy "offset"
memory_offset = AttrLabelProxy
#endif
getMemorySize :: MonadIO m => Memory -> m Word64
getMemorySize :: Memory -> m Word64
getMemorySize s :: Memory
s = IO Word64 -> m Word64
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word64 -> m Word64) -> IO Word64 -> m Word64
forall a b. (a -> b) -> a -> b
$ Memory -> (Ptr Memory -> IO Word64) -> IO Word64
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Memory
s ((Ptr Memory -> IO Word64) -> IO Word64)
-> (Ptr Memory -> IO Word64) -> IO Word64
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Memory
ptr -> do
Word64
val <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek (Ptr Memory
ptr Ptr Memory -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 104) :: IO Word64
Word64 -> IO Word64
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
val
setMemorySize :: MonadIO m => Memory -> Word64 -> m ()
setMemorySize :: Memory -> Word64 -> m ()
setMemorySize s :: Memory
s val :: Word64
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Memory -> (Ptr Memory -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Memory
s ((Ptr Memory -> IO ()) -> IO ()) -> (Ptr Memory -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Memory
ptr -> do
Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Memory
ptr Ptr Memory -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 104) (Word64
val :: Word64)
#if defined(ENABLE_OVERLOADING)
data MemorySizeFieldInfo
instance AttrInfo MemorySizeFieldInfo where
type AttrBaseTypeConstraint MemorySizeFieldInfo = (~) Memory
type AttrAllowedOps MemorySizeFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint MemorySizeFieldInfo = (~) Word64
type AttrTransferTypeConstraint MemorySizeFieldInfo = (~)Word64
type AttrTransferType MemorySizeFieldInfo = Word64
type AttrGetType MemorySizeFieldInfo = Word64
type AttrLabel MemorySizeFieldInfo = "size"
type AttrOrigin MemorySizeFieldInfo = Memory
attrGet = getMemorySize
attrSet = setMemorySize
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
memory_size :: AttrLabelProxy "size"
memory_size = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Memory
type instance O.AttributeList Memory = MemoryAttributeList
type MemoryAttributeList = ('[ '("miniObject", MemoryMiniObjectFieldInfo), '("allocator", MemoryAllocatorFieldInfo), '("parent", MemoryParentFieldInfo), '("maxsize", MemoryMaxsizeFieldInfo), '("align", MemoryAlignFieldInfo), '("offset", MemoryOffsetFieldInfo), '("size", MemorySizeFieldInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "gst_memory_new_wrapped" gst_memory_new_wrapped ::
CUInt ->
Ptr Word8 ->
Word64 ->
Word64 ->
Word64 ->
Ptr () ->
FunPtr GLib.Callbacks.C_DestroyNotify ->
IO (Ptr Memory)
memoryNewWrapped ::
(B.CallStack.HasCallStack, MonadIO m) =>
[Gst.Flags.MemoryFlags]
-> ByteString
-> Word64
-> Word64
-> Maybe (GLib.Callbacks.DestroyNotify)
-> m (Maybe Memory)
memoryNewWrapped :: [MemoryFlags]
-> ByteString
-> Word64
-> Word64
-> Maybe DestroyNotify
-> m (Maybe Memory)
memoryNewWrapped flags :: [MemoryFlags]
flags data_ :: ByteString
data_ maxsize :: Word64
maxsize offset :: Word64
offset notify :: Maybe DestroyNotify
notify = IO (Maybe Memory) -> m (Maybe Memory)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Memory) -> m (Maybe Memory))
-> IO (Maybe Memory) -> m (Maybe Memory)
forall a b. (a -> b) -> a -> b
$ do
let size :: Word64
size = Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word64) -> Int -> Word64
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
data_
let flags' :: CUInt
flags' = [MemoryFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [MemoryFlags]
flags
Ptr Word8
data_' <- ByteString -> IO (Ptr Word8)
packByteString ByteString
data_
FunPtr DestroyNotify
maybeNotify <- case Maybe DestroyNotify
notify of
Nothing -> FunPtr DestroyNotify -> IO (FunPtr DestroyNotify)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr DestroyNotify
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
Just jNotify :: DestroyNotify
jNotify -> do
Ptr (FunPtr DestroyNotify)
ptrnotify <- IO (Ptr (FunPtr DestroyNotify))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr GLib.Callbacks.C_DestroyNotify))
FunPtr DestroyNotify
jNotify' <- DestroyNotify -> IO (FunPtr DestroyNotify)
GLib.Callbacks.mk_DestroyNotify (Maybe (Ptr (FunPtr DestroyNotify))
-> DestroyNotify -> DestroyNotify
GLib.Callbacks.wrap_DestroyNotify (Ptr (FunPtr DestroyNotify) -> Maybe (Ptr (FunPtr DestroyNotify))
forall a. a -> Maybe a
Just Ptr (FunPtr DestroyNotify)
ptrnotify) DestroyNotify
jNotify)
Ptr (FunPtr DestroyNotify) -> FunPtr DestroyNotify -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr DestroyNotify)
ptrnotify FunPtr DestroyNotify
jNotify'
FunPtr DestroyNotify -> IO (FunPtr DestroyNotify)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr DestroyNotify
jNotify'
let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
Ptr Memory
result <- CUInt
-> Ptr Word8
-> Word64
-> Word64
-> Word64
-> Ptr ()
-> FunPtr DestroyNotify
-> IO (Ptr Memory)
gst_memory_new_wrapped CUInt
flags' Ptr Word8
data_' Word64
maxsize Word64
offset Word64
size Ptr ()
forall a. Ptr a
userData FunPtr DestroyNotify
maybeNotify
Maybe Memory
maybeResult <- Ptr Memory -> (Ptr Memory -> IO Memory) -> IO (Maybe Memory)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Memory
result ((Ptr Memory -> IO Memory) -> IO (Maybe Memory))
-> (Ptr Memory -> IO Memory) -> IO (Maybe Memory)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr Memory
result' -> do
Memory
result'' <- ((ManagedPtr Memory -> Memory) -> Ptr Memory -> IO Memory
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Memory -> Memory
Memory) Ptr Memory
result'
Memory -> IO Memory
forall (m :: * -> *) a. Monad m => a -> m a
return Memory
result''
Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
data_'
Maybe Memory -> IO (Maybe Memory)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Memory
maybeResult
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gst_memory_copy" gst_memory_copy ::
Ptr Memory ->
Int64 ->
Int64 ->
IO (Ptr Memory)
memoryCopy ::
(B.CallStack.HasCallStack, MonadIO m) =>
Memory
-> Int64
-> Int64
-> m Memory
memoryCopy :: Memory -> Int64 -> Int64 -> m Memory
memoryCopy mem :: Memory
mem offset :: Int64
offset size :: Int64
size = IO Memory -> m Memory
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Memory -> m Memory) -> IO Memory -> m Memory
forall a b. (a -> b) -> a -> b
$ do
Ptr Memory
mem' <- Memory -> IO (Ptr Memory)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Memory
mem
Ptr Memory
result <- Ptr Memory -> Int64 -> Int64 -> IO (Ptr Memory)
gst_memory_copy Ptr Memory
mem' Int64
offset Int64
size
Text -> Ptr Memory -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "memoryCopy" Ptr Memory
result
Memory
result' <- ((ManagedPtr Memory -> Memory) -> Ptr Memory -> IO Memory
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Memory -> Memory
Memory) Ptr Memory
result
Memory -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Memory
mem
Memory -> IO Memory
forall (m :: * -> *) a. Monad m => a -> m a
return Memory
result'
#if defined(ENABLE_OVERLOADING)
data MemoryCopyMethodInfo
instance (signature ~ (Int64 -> Int64 -> m Memory), MonadIO m) => O.MethodInfo MemoryCopyMethodInfo Memory signature where
overloadedMethod = memoryCopy
#endif
foreign import ccall "gst_memory_get_sizes" gst_memory_get_sizes ::
Ptr Memory ->
Ptr Word64 ->
Ptr Word64 ->
IO Word64
memoryGetSizes ::
(B.CallStack.HasCallStack, MonadIO m) =>
Memory
-> m ((Word64, Word64, Word64))
memoryGetSizes :: Memory -> m (Word64, Word64, Word64)
memoryGetSizes mem :: Memory
mem = IO (Word64, Word64, Word64) -> m (Word64, Word64, Word64)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Word64, Word64, Word64) -> m (Word64, Word64, Word64))
-> IO (Word64, Word64, Word64) -> m (Word64, Word64, Word64)
forall a b. (a -> b) -> a -> b
$ do
Ptr Memory
mem' <- Memory -> IO (Ptr Memory)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Memory
mem
Ptr Word64
offset <- IO (Ptr Word64)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word64)
Ptr Word64
maxsize <- IO (Ptr Word64)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word64)
Word64
result <- Ptr Memory -> Ptr Word64 -> Ptr Word64 -> IO Word64
gst_memory_get_sizes Ptr Memory
mem' Ptr Word64
offset Ptr Word64
maxsize
Word64
offset' <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek Ptr Word64
offset
Word64
maxsize' <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek Ptr Word64
maxsize
Memory -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Memory
mem
Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
offset
Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
maxsize
(Word64, Word64, Word64) -> IO (Word64, Word64, Word64)
forall (m :: * -> *) a. Monad m => a -> m a
return (Word64
result, Word64
offset', Word64
maxsize')
#if defined(ENABLE_OVERLOADING)
data MemoryGetSizesMethodInfo
instance (signature ~ (m ((Word64, Word64, Word64))), MonadIO m) => O.MethodInfo MemoryGetSizesMethodInfo Memory signature where
overloadedMethod = memoryGetSizes
#endif
foreign import ccall "gst_memory_is_span" gst_memory_is_span ::
Ptr Memory ->
Ptr Memory ->
Ptr Word64 ->
IO CInt
memoryIsSpan ::
(B.CallStack.HasCallStack, MonadIO m) =>
Memory
-> Memory
-> m ((Bool, Word64))
memoryIsSpan :: Memory -> Memory -> m (Bool, Word64)
memoryIsSpan mem1 :: Memory
mem1 mem2 :: Memory
mem2 = IO (Bool, Word64) -> m (Bool, Word64)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Word64) -> m (Bool, Word64))
-> IO (Bool, Word64) -> m (Bool, Word64)
forall a b. (a -> b) -> a -> b
$ do
Ptr Memory
mem1' <- Memory -> IO (Ptr Memory)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Memory
mem1
Ptr Memory
mem2' <- Memory -> IO (Ptr Memory)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Memory
mem2
Ptr Word64
offset <- IO (Ptr Word64)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word64)
CInt
result <- Ptr Memory -> Ptr Memory -> Ptr Word64 -> IO CInt
gst_memory_is_span Ptr Memory
mem1' Ptr Memory
mem2' Ptr Word64
offset
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
Word64
offset' <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek Ptr Word64
offset
Memory -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Memory
mem1
Memory -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Memory
mem2
Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
offset
(Bool, Word64) -> IO (Bool, Word64)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Word64
offset')
#if defined(ENABLE_OVERLOADING)
data MemoryIsSpanMethodInfo
instance (signature ~ (Memory -> m ((Bool, Word64))), MonadIO m) => O.MethodInfo MemoryIsSpanMethodInfo Memory signature where
overloadedMethod = memoryIsSpan
#endif
foreign import ccall "gst_memory_is_type" gst_memory_is_type ::
Ptr Memory ->
CString ->
IO CInt
memoryIsType ::
(B.CallStack.HasCallStack, MonadIO m) =>
Memory
-> T.Text
-> m Bool
memoryIsType :: Memory -> Text -> m Bool
memoryIsType mem :: Memory
mem memType :: Text
memType = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr Memory
mem' <- Memory -> IO (Ptr Memory)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Memory
mem
CString
memType' <- Text -> IO CString
textToCString Text
memType
CInt
result <- Ptr Memory -> CString -> IO CInt
gst_memory_is_type Ptr Memory
mem' CString
memType'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
Memory -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Memory
mem
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
memType'
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data MemoryIsTypeMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m) => O.MethodInfo MemoryIsTypeMethodInfo Memory signature where
overloadedMethod = memoryIsType
#endif
foreign import ccall "gst_memory_make_mapped" gst_memory_make_mapped ::
Ptr Memory ->
Ptr Gst.MapInfo.MapInfo ->
CUInt ->
IO (Ptr Memory)
memoryMakeMapped ::
(B.CallStack.HasCallStack, MonadIO m) =>
Memory
-> [Gst.Flags.MapFlags]
-> m ((Maybe Memory, Gst.MapInfo.MapInfo))
memoryMakeMapped :: Memory -> [MapFlags] -> m (Maybe Memory, MapInfo)
memoryMakeMapped mem :: Memory
mem flags :: [MapFlags]
flags = IO (Maybe Memory, MapInfo) -> m (Maybe Memory, MapInfo)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Memory, MapInfo) -> m (Maybe Memory, MapInfo))
-> IO (Maybe Memory, MapInfo) -> m (Maybe Memory, MapInfo)
forall a b. (a -> b) -> a -> b
$ do
Ptr Memory
mem' <- Memory -> IO (Ptr Memory)
forall a. (HasCallStack, BoxedObject a) => a -> IO (Ptr a)
B.ManagedPtr.disownBoxed Memory
mem
Ptr MapInfo
info <- Int -> IO (Ptr MapInfo)
forall a. Int -> IO (Ptr a)
callocBytes 104 :: IO (Ptr Gst.MapInfo.MapInfo)
let flags' :: CUInt
flags' = [MapFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [MapFlags]
flags
Ptr Memory
result <- Ptr Memory -> Ptr MapInfo -> CUInt -> IO (Ptr Memory)
gst_memory_make_mapped Ptr Memory
mem' Ptr MapInfo
info CUInt
flags'
Maybe Memory
maybeResult <- Ptr Memory -> (Ptr Memory -> IO Memory) -> IO (Maybe Memory)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Memory
result ((Ptr Memory -> IO Memory) -> IO (Maybe Memory))
-> (Ptr Memory -> IO Memory) -> IO (Maybe Memory)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr Memory
result' -> do
Memory
result'' <- ((ManagedPtr Memory -> Memory) -> Ptr Memory -> IO Memory
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Memory -> Memory
Memory) Ptr Memory
result'
Memory -> IO Memory
forall (m :: * -> *) a. Monad m => a -> m a
return Memory
result''
MapInfo
info' <- ((ManagedPtr MapInfo -> MapInfo) -> Ptr MapInfo -> IO MapInfo
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr MapInfo -> MapInfo
Gst.MapInfo.MapInfo) Ptr MapInfo
info
Memory -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Memory
mem
(Maybe Memory, MapInfo) -> IO (Maybe Memory, MapInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Memory
maybeResult, MapInfo
info')
#if defined(ENABLE_OVERLOADING)
data MemoryMakeMappedMethodInfo
instance (signature ~ ([Gst.Flags.MapFlags] -> m ((Maybe Memory, Gst.MapInfo.MapInfo))), MonadIO m) => O.MethodInfo MemoryMakeMappedMethodInfo Memory signature where
overloadedMethod = memoryMakeMapped
#endif
foreign import ccall "gst_memory_map" gst_memory_map ::
Ptr Memory ->
Ptr Gst.MapInfo.MapInfo ->
CUInt ->
IO CInt
memoryMap ::
(B.CallStack.HasCallStack, MonadIO m) =>
Memory
-> [Gst.Flags.MapFlags]
-> m ((Bool, Gst.MapInfo.MapInfo))
memoryMap :: Memory -> [MapFlags] -> m (Bool, MapInfo)
memoryMap mem :: Memory
mem flags :: [MapFlags]
flags = IO (Bool, MapInfo) -> m (Bool, MapInfo)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, MapInfo) -> m (Bool, MapInfo))
-> IO (Bool, MapInfo) -> m (Bool, MapInfo)
forall a b. (a -> b) -> a -> b
$ do
Ptr Memory
mem' <- Memory -> IO (Ptr Memory)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Memory
mem
Ptr MapInfo
info <- Int -> IO (Ptr MapInfo)
forall a. Int -> IO (Ptr a)
callocBytes 104 :: IO (Ptr Gst.MapInfo.MapInfo)
let flags' :: CUInt
flags' = [MapFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [MapFlags]
flags
CInt
result <- Ptr Memory -> Ptr MapInfo -> CUInt -> IO CInt
gst_memory_map Ptr Memory
mem' Ptr MapInfo
info CUInt
flags'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
MapInfo
info' <- ((ManagedPtr MapInfo -> MapInfo) -> Ptr MapInfo -> IO MapInfo
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr MapInfo -> MapInfo
Gst.MapInfo.MapInfo) Ptr MapInfo
info
Memory -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Memory
mem
(Bool, MapInfo) -> IO (Bool, MapInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', MapInfo
info')
#if defined(ENABLE_OVERLOADING)
data MemoryMapMethodInfo
instance (signature ~ ([Gst.Flags.MapFlags] -> m ((Bool, Gst.MapInfo.MapInfo))), MonadIO m) => O.MethodInfo MemoryMapMethodInfo Memory signature where
overloadedMethod = memoryMap
#endif
foreign import ccall "gst_memory_resize" gst_memory_resize ::
Ptr Memory ->
Int64 ->
Word64 ->
IO ()
memoryResize ::
(B.CallStack.HasCallStack, MonadIO m) =>
Memory
-> Int64
-> Word64
-> m ()
memoryResize :: Memory -> Int64 -> Word64 -> m ()
memoryResize mem :: Memory
mem offset :: Int64
offset size :: Word64
size = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Memory
mem' <- Memory -> IO (Ptr Memory)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Memory
mem
Ptr Memory -> Int64 -> Word64 -> IO ()
gst_memory_resize Ptr Memory
mem' Int64
offset Word64
size
Memory -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Memory
mem
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data MemoryResizeMethodInfo
instance (signature ~ (Int64 -> Word64 -> m ()), MonadIO m) => O.MethodInfo MemoryResizeMethodInfo Memory signature where
overloadedMethod = memoryResize
#endif
foreign import ccall "gst_memory_share" gst_memory_share ::
Ptr Memory ->
Int64 ->
Int64 ->
IO (Ptr Memory)
memoryShare ::
(B.CallStack.HasCallStack, MonadIO m) =>
Memory
-> Int64
-> Int64
-> m Memory
memoryShare :: Memory -> Int64 -> Int64 -> m Memory
memoryShare mem :: Memory
mem offset :: Int64
offset size :: Int64
size = IO Memory -> m Memory
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Memory -> m Memory) -> IO Memory -> m Memory
forall a b. (a -> b) -> a -> b
$ do
Ptr Memory
mem' <- Memory -> IO (Ptr Memory)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Memory
mem
Ptr Memory
result <- Ptr Memory -> Int64 -> Int64 -> IO (Ptr Memory)
gst_memory_share Ptr Memory
mem' Int64
offset Int64
size
Text -> Ptr Memory -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "memoryShare" Ptr Memory
result
Memory
result' <- ((ManagedPtr Memory -> Memory) -> Ptr Memory -> IO Memory
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Memory -> Memory
Memory) Ptr Memory
result
Memory -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Memory
mem
Memory -> IO Memory
forall (m :: * -> *) a. Monad m => a -> m a
return Memory
result'
#if defined(ENABLE_OVERLOADING)
data MemoryShareMethodInfo
instance (signature ~ (Int64 -> Int64 -> m Memory), MonadIO m) => O.MethodInfo MemoryShareMethodInfo Memory signature where
overloadedMethod = memoryShare
#endif
foreign import ccall "gst_memory_unmap" gst_memory_unmap ::
Ptr Memory ->
Ptr Gst.MapInfo.MapInfo ->
IO ()
memoryUnmap ::
(B.CallStack.HasCallStack, MonadIO m) =>
Memory
-> Gst.MapInfo.MapInfo
-> m ()
memoryUnmap :: Memory -> MapInfo -> m ()
memoryUnmap mem :: Memory
mem info :: MapInfo
info = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Memory
mem' <- Memory -> IO (Ptr Memory)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Memory
mem
Ptr MapInfo
info' <- MapInfo -> IO (Ptr MapInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MapInfo
info
Ptr Memory -> Ptr MapInfo -> IO ()
gst_memory_unmap Ptr Memory
mem' Ptr MapInfo
info'
Memory -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Memory
mem
MapInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MapInfo
info
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data MemoryUnmapMethodInfo
instance (signature ~ (Gst.MapInfo.MapInfo -> m ()), MonadIO m) => O.MethodInfo MemoryUnmapMethodInfo Memory signature where
overloadedMethod = memoryUnmap
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveMemoryMethod (t :: Symbol) (o :: *) :: * where
ResolveMemoryMethod "copy" o = MemoryCopyMethodInfo
ResolveMemoryMethod "isSpan" o = MemoryIsSpanMethodInfo
ResolveMemoryMethod "isType" o = MemoryIsTypeMethodInfo
ResolveMemoryMethod "makeMapped" o = MemoryMakeMappedMethodInfo
ResolveMemoryMethod "map" o = MemoryMapMethodInfo
ResolveMemoryMethod "resize" o = MemoryResizeMethodInfo
ResolveMemoryMethod "share" o = MemoryShareMethodInfo
ResolveMemoryMethod "unmap" o = MemoryUnmapMethodInfo
ResolveMemoryMethod "getSizes" o = MemoryGetSizesMethodInfo
ResolveMemoryMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveMemoryMethod t Memory, O.MethodInfo info Memory p) => OL.IsLabel t (Memory -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif