Copyright | Will Thompson, Iñaki García Etxebarria and Jonas Platte |
---|---|
License | LGPL-2.1 |
Maintainer | Iñaki García Etxebarria (garetxe@gmail.com) |
Safe Haskell | None |
Language | Haskell2010 |
GI.GstBase.Structs.ByteWriter
Contents
- Exported types
- Methods
- ensureFreeSpace
- fill
- free
- freeAndGetBuffer
- freeAndGetData
- getRemaining
- init
- initWithData
- initWithSize
- putBuffer
- putData
- putFloat32Be
- putFloat32Le
- putFloat64Be
- putFloat64Le
- putInt16Be
- putInt16Le
- putInt24Be
- putInt24Le
- putInt32Be
- putInt32Le
- putInt64Be
- putInt64Le
- putInt8
- putStringUtf16
- putStringUtf32
- putStringUtf8
- putUint16Be
- putUint16Le
- putUint24Be
- putUint24Le
- putUint32Be
- putUint32Le
- putUint64Be
- putUint64Le
- putUint8
- reset
- resetAndGetBuffer
- resetAndGetData
- Properties
Description
ByteWriter
provides a byte writer and reader that can write/read different
integer and floating point types to/from a memory buffer. It provides functions
for writing/reading signed/unsigned, little/big endian integers of 8, 16, 24,
32 and 64 bits and functions for reading little/big endian floating points numbers of
32 and 64 bits. It also provides functions to write/read NUL-terminated strings
in various character encodings.
- newtype ByteWriter = ByteWriter (ManagedPtr ByteWriter)
- newZeroByteWriter :: MonadIO m => m ByteWriter
- noByteWriter :: Maybe ByteWriter
- data ByteWriterEnsureFreeSpaceMethodInfo
- byteWriterEnsureFreeSpace :: (HasCallStack, MonadIO m) => ByteWriter -> Word32 -> m Bool
- data ByteWriterFillMethodInfo
- byteWriterFill :: (HasCallStack, MonadIO m) => ByteWriter -> Word8 -> Word32 -> m Bool
- data ByteWriterFreeMethodInfo
- byteWriterFree :: (HasCallStack, MonadIO m) => ByteWriter -> m ()
- data ByteWriterFreeAndGetBufferMethodInfo
- byteWriterFreeAndGetBuffer :: (HasCallStack, MonadIO m) => ByteWriter -> m Buffer
- data ByteWriterFreeAndGetDataMethodInfo
- byteWriterFreeAndGetData :: (HasCallStack, MonadIO m) => ByteWriter -> m Word8
- data ByteWriterGetRemainingMethodInfo
- byteWriterGetRemaining :: (HasCallStack, MonadIO m) => ByteWriter -> m Word32
- data ByteWriterInitMethodInfo
- byteWriterInit :: (HasCallStack, MonadIO m) => ByteWriter -> m ()
- data ByteWriterInitWithDataMethodInfo
- byteWriterInitWithData :: (HasCallStack, MonadIO m) => ByteWriter -> ByteString -> Bool -> m ()
- data ByteWriterInitWithSizeMethodInfo
- byteWriterInitWithSize :: (HasCallStack, MonadIO m) => ByteWriter -> Word32 -> Bool -> m ()
- data ByteWriterPutBufferMethodInfo
- byteWriterPutBuffer :: (HasCallStack, MonadIO m) => ByteWriter -> Buffer -> Word64 -> Int64 -> m Bool
- data ByteWriterPutDataMethodInfo
- byteWriterPutData :: (HasCallStack, MonadIO m) => ByteWriter -> ByteString -> m Bool
- data ByteWriterPutFloat32BeMethodInfo
- byteWriterPutFloat32Be :: (HasCallStack, MonadIO m) => ByteWriter -> Float -> m Bool
- data ByteWriterPutFloat32LeMethodInfo
- byteWriterPutFloat32Le :: (HasCallStack, MonadIO m) => ByteWriter -> Float -> m Bool
- data ByteWriterPutFloat64BeMethodInfo
- byteWriterPutFloat64Be :: (HasCallStack, MonadIO m) => ByteWriter -> Double -> m Bool
- data ByteWriterPutFloat64LeMethodInfo
- byteWriterPutFloat64Le :: (HasCallStack, MonadIO m) => ByteWriter -> Double -> m Bool
- data ByteWriterPutInt16BeMethodInfo
- byteWriterPutInt16Be :: (HasCallStack, MonadIO m) => ByteWriter -> Int16 -> m Bool
- data ByteWriterPutInt16LeMethodInfo
- byteWriterPutInt16Le :: (HasCallStack, MonadIO m) => ByteWriter -> Int16 -> m Bool
- data ByteWriterPutInt24BeMethodInfo
- byteWriterPutInt24Be :: (HasCallStack, MonadIO m) => ByteWriter -> Int32 -> m Bool
- data ByteWriterPutInt24LeMethodInfo
- byteWriterPutInt24Le :: (HasCallStack, MonadIO m) => ByteWriter -> Int32 -> m Bool
- data ByteWriterPutInt32BeMethodInfo
- byteWriterPutInt32Be :: (HasCallStack, MonadIO m) => ByteWriter -> Int32 -> m Bool
- data ByteWriterPutInt32LeMethodInfo
- byteWriterPutInt32Le :: (HasCallStack, MonadIO m) => ByteWriter -> Int32 -> m Bool
- data ByteWriterPutInt64BeMethodInfo
- byteWriterPutInt64Be :: (HasCallStack, MonadIO m) => ByteWriter -> Int64 -> m Bool
- data ByteWriterPutInt64LeMethodInfo
- byteWriterPutInt64Le :: (HasCallStack, MonadIO m) => ByteWriter -> Int64 -> m Bool
- data ByteWriterPutInt8MethodInfo
- byteWriterPutInt8 :: (HasCallStack, MonadIO m) => ByteWriter -> Int8 -> m Bool
- data ByteWriterPutStringUtf16MethodInfo
- byteWriterPutStringUtf16 :: (HasCallStack, MonadIO m) => ByteWriter -> [Word16] -> m Bool
- data ByteWriterPutStringUtf32MethodInfo
- byteWriterPutStringUtf32 :: (HasCallStack, MonadIO m) => ByteWriter -> [Word32] -> m Bool
- data ByteWriterPutStringUtf8MethodInfo
- byteWriterPutStringUtf8 :: (HasCallStack, MonadIO m) => ByteWriter -> [Text] -> m Bool
- data ByteWriterPutUint16BeMethodInfo
- byteWriterPutUint16Be :: (HasCallStack, MonadIO m) => ByteWriter -> Word16 -> m Bool
- data ByteWriterPutUint16LeMethodInfo
- byteWriterPutUint16Le :: (HasCallStack, MonadIO m) => ByteWriter -> Word16 -> m Bool
- data ByteWriterPutUint24BeMethodInfo
- byteWriterPutUint24Be :: (HasCallStack, MonadIO m) => ByteWriter -> Word32 -> m Bool
- data ByteWriterPutUint24LeMethodInfo
- byteWriterPutUint24Le :: (HasCallStack, MonadIO m) => ByteWriter -> Word32 -> m Bool
- data ByteWriterPutUint32BeMethodInfo
- byteWriterPutUint32Be :: (HasCallStack, MonadIO m) => ByteWriter -> Word32 -> m Bool
- data ByteWriterPutUint32LeMethodInfo
- byteWriterPutUint32Le :: (HasCallStack, MonadIO m) => ByteWriter -> Word32 -> m Bool
- data ByteWriterPutUint64BeMethodInfo
- byteWriterPutUint64Be :: (HasCallStack, MonadIO m) => ByteWriter -> Word64 -> m Bool
- data ByteWriterPutUint64LeMethodInfo
- byteWriterPutUint64Le :: (HasCallStack, MonadIO m) => ByteWriter -> Word64 -> m Bool
- data ByteWriterPutUint8MethodInfo
- byteWriterPutUint8 :: (HasCallStack, MonadIO m) => ByteWriter -> Word8 -> m Bool
- data ByteWriterResetMethodInfo
- byteWriterReset :: (HasCallStack, MonadIO m) => ByteWriter -> m ()
- data ByteWriterResetAndGetBufferMethodInfo
- byteWriterResetAndGetBuffer :: (HasCallStack, MonadIO m) => ByteWriter -> m Buffer
- data ByteWriterResetAndGetDataMethodInfo
- byteWriterResetAndGetData :: (HasCallStack, MonadIO m) => ByteWriter -> m (Ptr Word8)
- byteWriter_allocSize :: AttrLabelProxy "allocSize"
- getByteWriterAllocSize :: MonadIO m => ByteWriter -> m Word32
- setByteWriterAllocSize :: MonadIO m => ByteWriter -> Word32 -> m ()
- byteWriter_fixed :: AttrLabelProxy "fixed"
- getByteWriterFixed :: MonadIO m => ByteWriter -> m Bool
- setByteWriterFixed :: MonadIO m => ByteWriter -> Bool -> m ()
- byteWriter_owned :: AttrLabelProxy "owned"
- getByteWriterOwned :: MonadIO m => ByteWriter -> m Bool
- setByteWriterOwned :: MonadIO m => ByteWriter -> Bool -> m ()
- byteWriter_parent :: AttrLabelProxy "parent"
- getByteWriterParent :: MonadIO m => ByteWriter -> m ByteReader
Exported types
newtype ByteWriter Source #
Constructors
ByteWriter (ManagedPtr ByteWriter) |
Instances
newZeroByteWriter :: MonadIO m => m ByteWriter Source #
Construct a ByteWriter
struct initialized to zero.
Methods
ensureFreeSpace
data ByteWriterEnsureFreeSpaceMethodInfo Source #
Instances
((~) * signature (Word32 -> m Bool), MonadIO m) => MethodInfo * ByteWriterEnsureFreeSpaceMethodInfo ByteWriter signature Source # | |
byteWriterEnsureFreeSpace Source #
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> Word32 |
|
-> m Bool | Returns: |
Checks if enough free space from the current write cursor is available and reallocates if necessary.
fill
data ByteWriterFillMethodInfo Source #
Instances
((~) * signature (Word8 -> Word32 -> m Bool), MonadIO m) => MethodInfo * ByteWriterFillMethodInfo ByteWriter signature Source # | |
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> Word8 |
|
-> Word32 |
|
-> m Bool | Returns: |
Writes size
bytes containing value
to writer
.
free
data ByteWriterFreeMethodInfo Source #
Instances
((~) * signature (m ()), MonadIO m) => MethodInfo * ByteWriterFreeMethodInfo ByteWriter signature Source # | |
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> m () |
Frees writer
and all memory allocated by it.
freeAndGetBuffer
data ByteWriterFreeAndGetBufferMethodInfo Source #
Instances
((~) * signature (m Buffer), MonadIO m) => MethodInfo * ByteWriterFreeAndGetBufferMethodInfo ByteWriter signature Source # | |
byteWriterFreeAndGetBuffer Source #
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> m Buffer | Returns: the current data as buffer. |
Frees writer
and all memory allocated by it except
the current data, which is returned as Buffer
.
Free-function: gst_buffer_unref
freeAndGetData
data ByteWriterFreeAndGetDataMethodInfo Source #
Instances
((~) * signature (m Word8), MonadIO m) => MethodInfo * ByteWriterFreeAndGetDataMethodInfo ByteWriter signature Source # | |
byteWriterFreeAndGetData Source #
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> m Word8 | Returns: the current data. |
Frees writer
and all memory allocated by it except
the current data, which is returned.
Free-function: g_free
getRemaining
data ByteWriterGetRemainingMethodInfo Source #
Instances
((~) * signature (m Word32), MonadIO m) => MethodInfo * ByteWriterGetRemainingMethodInfo ByteWriter signature Source # | |
byteWriterGetRemaining Source #
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> m Word32 | Returns: the remaining size of data that can still be written |
Returns the remaining size of data that can still be written. If -1 is returned the remaining size is only limited by system resources.
init
data ByteWriterInitMethodInfo Source #
Instances
((~) * signature (m ()), MonadIO m) => MethodInfo * ByteWriterInitMethodInfo ByteWriter signature Source # | |
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> m () |
Initializes writer
to an empty instance
initWithData
data ByteWriterInitWithDataMethodInfo Source #
Instances
((~) * signature (ByteString -> Bool -> m ()), MonadIO m) => MethodInfo * ByteWriterInitWithDataMethodInfo ByteWriter signature Source # | |
byteWriterInitWithData Source #
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> ByteString |
|
-> Bool |
|
-> m () |
Initializes writer
with the given
memory area. If initialized
is True
it is possible to
read size
bytes from the ByteWriter
from the beginning.
initWithSize
data ByteWriterInitWithSizeMethodInfo Source #
Instances
((~) * signature (Word32 -> Bool -> m ()), MonadIO m) => MethodInfo * ByteWriterInitWithSizeMethodInfo ByteWriter signature Source # | |
byteWriterInitWithSize Source #
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> Word32 |
|
-> Bool |
|
-> m () |
Initializes writer
with the given initial data size.
putBuffer
data ByteWriterPutBufferMethodInfo Source #
Instances
((~) * signature (Buffer -> Word64 -> Int64 -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutBufferMethodInfo ByteWriter signature Source # | |
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> Buffer |
|
-> Word64 |
|
-> Int64 |
|
-> m Bool | Returns: |
Writes size
bytes of data
to writer
.
putData
data ByteWriterPutDataMethodInfo Source #
Instances
((~) * signature (ByteString -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutDataMethodInfo ByteWriter signature Source # | |
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> ByteString |
|
-> m Bool | Returns: |
Writes size
bytes of data
to writer
.
putFloat32Be
data ByteWriterPutFloat32BeMethodInfo Source #
Instances
((~) * signature (Float -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutFloat32BeMethodInfo ByteWriter signature Source # | |
byteWriterPutFloat32Be Source #
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> Float |
|
-> m Bool | Returns: |
Writes a big endian 32 bit float to writer
.
putFloat32Le
data ByteWriterPutFloat32LeMethodInfo Source #
Instances
((~) * signature (Float -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutFloat32LeMethodInfo ByteWriter signature Source # | |
byteWriterPutFloat32Le Source #
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> Float |
|
-> m Bool | Returns: |
Writes a little endian 32 bit float to writer
.
putFloat64Be
data ByteWriterPutFloat64BeMethodInfo Source #
Instances
((~) * signature (Double -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutFloat64BeMethodInfo ByteWriter signature Source # | |
byteWriterPutFloat64Be Source #
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> Double |
|
-> m Bool | Returns: |
Writes a big endian 64 bit float to writer
.
putFloat64Le
data ByteWriterPutFloat64LeMethodInfo Source #
Instances
((~) * signature (Double -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutFloat64LeMethodInfo ByteWriter signature Source # | |
byteWriterPutFloat64Le Source #
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> Double |
|
-> m Bool | Returns: |
Writes a little endian 64 bit float to writer
.
putInt16Be
data ByteWriterPutInt16BeMethodInfo Source #
Instances
((~) * signature (Int16 -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutInt16BeMethodInfo ByteWriter signature Source # | |
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> Int16 |
|
-> m Bool | Returns: |
Writes a signed big endian 16 bit integer to writer
.
putInt16Le
data ByteWriterPutInt16LeMethodInfo Source #
Instances
((~) * signature (Int16 -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutInt16LeMethodInfo ByteWriter signature Source # | |
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> Int16 |
|
-> m Bool | Returns: |
Writes a signed little endian 16 bit integer to writer
.
putInt24Be
data ByteWriterPutInt24BeMethodInfo Source #
Instances
((~) * signature (Int32 -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutInt24BeMethodInfo ByteWriter signature Source # | |
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> Int32 |
|
-> m Bool | Returns: |
Writes a signed big endian 24 bit integer to writer
.
putInt24Le
data ByteWriterPutInt24LeMethodInfo Source #
Instances
((~) * signature (Int32 -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutInt24LeMethodInfo ByteWriter signature Source # | |
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> Int32 |
|
-> m Bool | Returns: |
Writes a signed little endian 24 bit integer to writer
.
putInt32Be
data ByteWriterPutInt32BeMethodInfo Source #
Instances
((~) * signature (Int32 -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutInt32BeMethodInfo ByteWriter signature Source # | |
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> Int32 |
|
-> m Bool | Returns: |
Writes a signed big endian 32 bit integer to writer
.
putInt32Le
data ByteWriterPutInt32LeMethodInfo Source #
Instances
((~) * signature (Int32 -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutInt32LeMethodInfo ByteWriter signature Source # | |
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> Int32 |
|
-> m Bool | Returns: |
Writes a signed little endian 32 bit integer to writer
.
putInt64Be
data ByteWriterPutInt64BeMethodInfo Source #
Instances
((~) * signature (Int64 -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutInt64BeMethodInfo ByteWriter signature Source # | |
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> Int64 |
|
-> m Bool | Returns: |
Writes a signed big endian 64 bit integer to writer
.
putInt64Le
data ByteWriterPutInt64LeMethodInfo Source #
Instances
((~) * signature (Int64 -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutInt64LeMethodInfo ByteWriter signature Source # | |
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> Int64 |
|
-> m Bool | Returns: |
Writes a signed little endian 64 bit integer to writer
.
putInt8
data ByteWriterPutInt8MethodInfo Source #
Instances
((~) * signature (Int8 -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutInt8MethodInfo ByteWriter signature Source # | |
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> Int8 |
|
-> m Bool | Returns: |
Writes a signed 8 bit integer to writer
.
putStringUtf16
data ByteWriterPutStringUtf16MethodInfo Source #
Instances
((~) * signature ([Word16] -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutStringUtf16MethodInfo ByteWriter signature Source # | |
byteWriterPutStringUtf16 Source #
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> [Word16] |
|
-> m Bool | Returns: |
Writes a NUL-terminated UTF16 string to writer
(including the terminator).
putStringUtf32
data ByteWriterPutStringUtf32MethodInfo Source #
Instances
((~) * signature ([Word32] -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutStringUtf32MethodInfo ByteWriter signature Source # | |
byteWriterPutStringUtf32 Source #
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> [Word32] |
|
-> m Bool | Returns: |
Writes a NUL-terminated UTF32 string to writer
(including the terminator).
putStringUtf8
data ByteWriterPutStringUtf8MethodInfo Source #
Instances
((~) * signature ([Text] -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutStringUtf8MethodInfo ByteWriter signature Source # | |
byteWriterPutStringUtf8 Source #
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> [Text] |
|
-> m Bool | Returns: |
Writes a NUL-terminated UTF8 string to writer
(including the terminator).
putUint16Be
data ByteWriterPutUint16BeMethodInfo Source #
Instances
((~) * signature (Word16 -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutUint16BeMethodInfo ByteWriter signature Source # | |
byteWriterPutUint16Be Source #
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> Word16 |
|
-> m Bool | Returns: |
Writes a unsigned big endian 16 bit integer to writer
.
putUint16Le
data ByteWriterPutUint16LeMethodInfo Source #
Instances
((~) * signature (Word16 -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutUint16LeMethodInfo ByteWriter signature Source # | |
byteWriterPutUint16Le Source #
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> Word16 |
|
-> m Bool | Returns: |
Writes a unsigned little endian 16 bit integer to writer
.
putUint24Be
data ByteWriterPutUint24BeMethodInfo Source #
Instances
((~) * signature (Word32 -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutUint24BeMethodInfo ByteWriter signature Source # | |
byteWriterPutUint24Be Source #
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> Word32 |
|
-> m Bool | Returns: |
Writes a unsigned big endian 24 bit integer to writer
.
putUint24Le
data ByteWriterPutUint24LeMethodInfo Source #
Instances
((~) * signature (Word32 -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutUint24LeMethodInfo ByteWriter signature Source # | |
byteWriterPutUint24Le Source #
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> Word32 |
|
-> m Bool | Returns: |
Writes a unsigned little endian 24 bit integer to writer
.
putUint32Be
data ByteWriterPutUint32BeMethodInfo Source #
Instances
((~) * signature (Word32 -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutUint32BeMethodInfo ByteWriter signature Source # | |
byteWriterPutUint32Be Source #
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> Word32 |
|
-> m Bool | Returns: |
Writes a unsigned big endian 32 bit integer to writer
.
putUint32Le
data ByteWriterPutUint32LeMethodInfo Source #
Instances
((~) * signature (Word32 -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutUint32LeMethodInfo ByteWriter signature Source # | |
byteWriterPutUint32Le Source #
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> Word32 |
|
-> m Bool | Returns: |
Writes a unsigned little endian 32 bit integer to writer
.
putUint64Be
data ByteWriterPutUint64BeMethodInfo Source #
Instances
((~) * signature (Word64 -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutUint64BeMethodInfo ByteWriter signature Source # | |
byteWriterPutUint64Be Source #
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> Word64 |
|
-> m Bool | Returns: |
Writes a unsigned big endian 64 bit integer to writer
.
putUint64Le
data ByteWriterPutUint64LeMethodInfo Source #
Instances
((~) * signature (Word64 -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutUint64LeMethodInfo ByteWriter signature Source # | |
byteWriterPutUint64Le Source #
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> Word64 |
|
-> m Bool | Returns: |
Writes a unsigned little endian 64 bit integer to writer
.
putUint8
data ByteWriterPutUint8MethodInfo Source #
Instances
((~) * signature (Word8 -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutUint8MethodInfo ByteWriter signature Source # | |
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> Word8 |
|
-> m Bool | Returns: |
Writes a unsigned 8 bit integer to writer
.
reset
data ByteWriterResetMethodInfo Source #
Instances
((~) * signature (m ()), MonadIO m) => MethodInfo * ByteWriterResetMethodInfo ByteWriter signature Source # | |
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> m () |
Resets writer
and frees the data if it's
owned by writer
.
resetAndGetBuffer
data ByteWriterResetAndGetBufferMethodInfo Source #
Instances
((~) * signature (m Buffer), MonadIO m) => MethodInfo * ByteWriterResetAndGetBufferMethodInfo ByteWriter signature Source # | |
byteWriterResetAndGetBuffer Source #
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> m Buffer | Returns: the current data as buffer. |
Resets writer
and returns the current data as buffer.
Free-function: gst_buffer_unref
resetAndGetData
data ByteWriterResetAndGetDataMethodInfo Source #
Instances
((~) * signature (m (Ptr Word8)), MonadIO m) => MethodInfo * ByteWriterResetAndGetDataMethodInfo ByteWriter signature Source # | |
byteWriterResetAndGetData Source #
Arguments
:: (HasCallStack, MonadIO m) | |
=> ByteWriter |
|
-> m (Ptr Word8) | Returns: the current data. |
Resets writer
and returns the current data.
Free-function: g_free
Properties
allocSize
byteWriter_allocSize :: AttrLabelProxy "allocSize" Source #
getByteWriterAllocSize :: MonadIO m => ByteWriter -> m Word32 Source #
setByteWriterAllocSize :: MonadIO m => ByteWriter -> Word32 -> m () Source #
fixed
byteWriter_fixed :: AttrLabelProxy "fixed" Source #
getByteWriterFixed :: MonadIO m => ByteWriter -> m Bool Source #
setByteWriterFixed :: MonadIO m => ByteWriter -> Bool -> m () Source #
owned
byteWriter_owned :: AttrLabelProxy "owned" Source #
getByteWriterOwned :: MonadIO m => ByteWriter -> m Bool Source #
setByteWriterOwned :: MonadIO m => ByteWriter -> Bool -> m () Source #
parent
byteWriter_parent :: AttrLabelProxy "parent" Source #
getByteWriterParent :: MonadIO m => ByteWriter -> m ByteReader Source #