gi-gstbase-1.0.11: GStreamerBase bindings

CopyrightWill Thompson, Iñaki García Etxebarria and Jonas Platte
LicenseLGPL-2.1
MaintainerIñaki García Etxebarria (garetxe@gmail.com)
Safe HaskellNone
LanguageHaskell2010

GI.GstBase.Structs.ByteWriter

Contents

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.

Synopsis

Exported types

newtype ByteWriter Source #

Instances

WrappedPtr ByteWriter Source # 
(~) AttrOpTag tag AttrSet => Constructible ByteWriter tag Source # 
((~) * info (ResolveByteWriterMethod t ByteWriter), MethodInfo * info ByteWriter p) => IsLabel t (ByteWriter -> p) Source # 

Methods

fromLabel :: Proxy# Symbol t -> ByteWriter -> p #

((~) * info (ResolveByteWriterMethod t ByteWriter), MethodInfo * info ByteWriter p) => IsLabelProxy t (ByteWriter -> p) Source # 

Methods

fromLabelProxy :: Proxy Symbol t -> ByteWriter -> p #

HasAttributeList * ByteWriter Source # 
((~) * signature (m (Ptr Word8)), MonadIO m) => MethodInfo * ByteWriterResetAndGetDataMethodInfo ByteWriter signature Source # 
((~) * signature (m Buffer), MonadIO m) => MethodInfo * ByteWriterResetAndGetBufferMethodInfo ByteWriter signature Source # 
((~) * signature (m ()), MonadIO m) => MethodInfo * ByteWriterResetMethodInfo ByteWriter signature Source # 
((~) * signature (Word8 -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutUint8MethodInfo ByteWriter signature Source # 
((~) * signature (Word64 -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutUint64LeMethodInfo ByteWriter signature Source # 
((~) * signature (Word64 -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutUint64BeMethodInfo ByteWriter signature Source # 
((~) * signature (Word32 -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutUint32LeMethodInfo ByteWriter signature Source # 
((~) * signature (Word32 -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutUint32BeMethodInfo ByteWriter signature Source # 
((~) * signature (Word32 -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutUint24LeMethodInfo ByteWriter signature Source # 
((~) * signature (Word32 -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutUint24BeMethodInfo ByteWriter signature Source # 
((~) * signature (Word16 -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutUint16LeMethodInfo ByteWriter signature Source # 
((~) * signature (Word16 -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutUint16BeMethodInfo ByteWriter signature Source # 
((~) * signature ([Text] -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutStringUtf8MethodInfo ByteWriter signature Source # 
((~) * signature ([Word32] -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutStringUtf32MethodInfo ByteWriter signature Source # 
((~) * signature ([Word16] -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutStringUtf16MethodInfo ByteWriter signature Source # 
((~) * signature (Int8 -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutInt8MethodInfo ByteWriter signature Source # 
((~) * signature (Int64 -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutInt64LeMethodInfo ByteWriter signature Source # 
((~) * signature (Int64 -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutInt64BeMethodInfo ByteWriter signature Source # 
((~) * signature (Int32 -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutInt32LeMethodInfo ByteWriter signature Source # 
((~) * signature (Int32 -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutInt32BeMethodInfo ByteWriter signature Source # 
((~) * signature (Int32 -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutInt24LeMethodInfo ByteWriter signature Source # 
((~) * signature (Int32 -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutInt24BeMethodInfo ByteWriter signature Source # 
((~) * signature (Int16 -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutInt16LeMethodInfo ByteWriter signature Source # 
((~) * signature (Int16 -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutInt16BeMethodInfo ByteWriter signature Source # 
((~) * signature (Double -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutFloat64LeMethodInfo ByteWriter signature Source # 
((~) * signature (Double -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutFloat64BeMethodInfo ByteWriter signature Source # 
((~) * signature (Float -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutFloat32LeMethodInfo ByteWriter signature Source # 
((~) * signature (Float -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutFloat32BeMethodInfo ByteWriter signature Source # 
((~) * signature (ByteString -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutDataMethodInfo ByteWriter signature Source # 
((~) * signature (Buffer -> Word64 -> Int64 -> m Bool), MonadIO m) => MethodInfo * ByteWriterPutBufferMethodInfo ByteWriter signature Source # 
((~) * signature (Word32 -> Bool -> m ()), MonadIO m) => MethodInfo * ByteWriterInitWithSizeMethodInfo ByteWriter signature Source # 
((~) * signature (ByteString -> Bool -> m ()), MonadIO m) => MethodInfo * ByteWriterInitWithDataMethodInfo ByteWriter signature Source # 
((~) * signature (m ()), MonadIO m) => MethodInfo * ByteWriterInitMethodInfo ByteWriter signature Source # 
((~) * signature (m Word32), MonadIO m) => MethodInfo * ByteWriterGetRemainingMethodInfo ByteWriter signature Source # 
((~) * signature (m Word8), MonadIO m) => MethodInfo * ByteWriterFreeAndGetDataMethodInfo ByteWriter signature Source # 
((~) * signature (m Buffer), MonadIO m) => MethodInfo * ByteWriterFreeAndGetBufferMethodInfo ByteWriter signature Source # 
((~) * signature (m ()), MonadIO m) => MethodInfo * ByteWriterFreeMethodInfo ByteWriter signature Source # 
((~) * signature (Word8 -> Word32 -> m Bool), MonadIO m) => MethodInfo * ByteWriterFillMethodInfo ByteWriter signature Source # 
((~) * signature (Word32 -> m Bool), MonadIO m) => MethodInfo * ByteWriterEnsureFreeSpaceMethodInfo ByteWriter signature Source # 
type AttributeList ByteWriter Source # 

newZeroByteWriter :: MonadIO m => m ByteWriter Source #

Construct a ByteWriter struct initialized to zero.

Methods

ensureFreeSpace

byteWriterEnsureFreeSpace Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> Word32

size: Number of bytes that should be available

-> m Bool

Returns: True if at least size bytes are still available

Checks if enough free space from the current write cursor is available and reallocates if necessary.

fill

byteWriterFill Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> Word8

value: Value to be written

-> Word32

size: Number of bytes to be written

-> m Bool

Returns: True if the value could be written

Writes size bytes containing value to writer.

free

byteWriterFree Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> m () 

Frees writer and all memory allocated by it.

freeAndGetBuffer

byteWriterFreeAndGetBuffer Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> m Buffer

Returns: the current data as buffer. gst_buffer_unref() after usage.

Frees writer and all memory allocated by it except the current data, which is returned as Buffer.

Free-function: gst_buffer_unref

freeAndGetData

byteWriterFreeAndGetData Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> m Word8

Returns: the current data. free after usage.

Frees writer and all memory allocated by it except the current data, which is returned.

Free-function: g_free

getRemaining

byteWriterGetRemaining Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> 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

byteWriterInit Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> m () 

Initializes writer to an empty instance

initWithData

byteWriterInitWithData Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> ByteString

data: Memory area for writing

-> Bool

initialized: If True the complete data can be read from the beginning

-> 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

byteWriterInitWithSize Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> Word32

size: Initial size of data

-> Bool

fixed: If True the data can't be reallocated

-> m () 

Initializes writer with the given initial data size.

putBuffer

byteWriterPutBuffer Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> Buffer

buffer: source Buffer

-> Word64

offset: offset to copy from

-> Int64

size: total size to copy. If -1, all data is copied

-> m Bool

Returns: True if the data could be written

Writes size bytes of data to writer.

putData

byteWriterPutData Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> ByteString

data: Data to write

-> m Bool

Returns: True if the value could be written

Writes size bytes of data to writer.

putFloat32Be

byteWriterPutFloat32Be Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> Float

val: Value to write

-> m Bool

Returns: True if the value could be written

Writes a big endian 32 bit float to writer.

putFloat32Le

byteWriterPutFloat32Le Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> Float

val: Value to write

-> m Bool

Returns: True if the value could be written

Writes a little endian 32 bit float to writer.

putFloat64Be

byteWriterPutFloat64Be Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> Double

val: Value to write

-> m Bool

Returns: True if the value could be written

Writes a big endian 64 bit float to writer.

putFloat64Le

byteWriterPutFloat64Le Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> Double

val: Value to write

-> m Bool

Returns: True if the value could be written

Writes a little endian 64 bit float to writer.

putInt16Be

byteWriterPutInt16Be Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> Int16

val: Value to write

-> m Bool

Returns: True if the value could be written

Writes a signed big endian 16 bit integer to writer.

putInt16Le

byteWriterPutInt16Le Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> Int16

val: Value to write

-> m Bool

Returns: True if the value could be written

Writes a signed little endian 16 bit integer to writer.

putInt24Be

byteWriterPutInt24Be Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> Int32

val: Value to write

-> m Bool

Returns: True if the value could be written

Writes a signed big endian 24 bit integer to writer.

putInt24Le

byteWriterPutInt24Le Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> Int32

val: Value to write

-> m Bool

Returns: True if the value could be written

Writes a signed little endian 24 bit integer to writer.

putInt32Be

byteWriterPutInt32Be Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> Int32

val: Value to write

-> m Bool

Returns: True if the value could be written

Writes a signed big endian 32 bit integer to writer.

putInt32Le

byteWriterPutInt32Le Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> Int32

val: Value to write

-> m Bool

Returns: True if the value could be written

Writes a signed little endian 32 bit integer to writer.

putInt64Be

byteWriterPutInt64Be Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> Int64

val: Value to write

-> m Bool

Returns: True if the value could be written

Writes a signed big endian 64 bit integer to writer.

putInt64Le

byteWriterPutInt64Le Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> Int64

val: Value to write

-> m Bool

Returns: True if the value could be written

Writes a signed little endian 64 bit integer to writer.

putInt8

byteWriterPutInt8 Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> Int8

val: Value to write

-> m Bool

Returns: True if the value could be written

Writes a signed 8 bit integer to writer.

putStringUtf16

byteWriterPutStringUtf16 Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> [Word16]

data: UTF16 string to write

-> m Bool

Returns: True if the value could be written

Writes a NUL-terminated UTF16 string to writer (including the terminator).

putStringUtf32

byteWriterPutStringUtf32 Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> [Word32]

data: UTF32 string to write

-> m Bool

Returns: True if the value could be written

Writes a NUL-terminated UTF32 string to writer (including the terminator).

putStringUtf8

byteWriterPutStringUtf8 Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> [Text]

data: UTF8 string to write

-> m Bool

Returns: True if the value could be written

Writes a NUL-terminated UTF8 string to writer (including the terminator).

putUint16Be

byteWriterPutUint16Be Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> Word16

val: Value to write

-> m Bool

Returns: True if the value could be written

Writes a unsigned big endian 16 bit integer to writer.

putUint16Le

byteWriterPutUint16Le Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> Word16

val: Value to write

-> m Bool

Returns: True if the value could be written

Writes a unsigned little endian 16 bit integer to writer.

putUint24Be

byteWriterPutUint24Be Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> Word32

val: Value to write

-> m Bool

Returns: True if the value could be written

Writes a unsigned big endian 24 bit integer to writer.

putUint24Le

byteWriterPutUint24Le Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> Word32

val: Value to write

-> m Bool

Returns: True if the value could be written

Writes a unsigned little endian 24 bit integer to writer.

putUint32Be

byteWriterPutUint32Be Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> Word32

val: Value to write

-> m Bool

Returns: True if the value could be written

Writes a unsigned big endian 32 bit integer to writer.

putUint32Le

byteWriterPutUint32Le Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> Word32

val: Value to write

-> m Bool

Returns: True if the value could be written

Writes a unsigned little endian 32 bit integer to writer.

putUint64Be

byteWriterPutUint64Be Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> Word64

val: Value to write

-> m Bool

Returns: True if the value could be written

Writes a unsigned big endian 64 bit integer to writer.

putUint64Le

byteWriterPutUint64Le Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> Word64

val: Value to write

-> m Bool

Returns: True if the value could be written

Writes a unsigned little endian 64 bit integer to writer.

putUint8

byteWriterPutUint8 Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> Word8

val: Value to write

-> m Bool

Returns: True if the value could be written

Writes a unsigned 8 bit integer to writer.

reset

byteWriterReset Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> m () 

Resets writer and frees the data if it's owned by writer.

resetAndGetBuffer

byteWriterResetAndGetBuffer Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> m Buffer

Returns: the current data as buffer. gst_buffer_unref() after usage.

Resets writer and returns the current data as buffer.

Free-function: gst_buffer_unref

resetAndGetData

byteWriterResetAndGetData Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> ByteWriter

writer: ByteWriter instance

-> m (Ptr Word8)

Returns: the current data. free after usage.

Resets writer and returns the current data.

Free-function: g_free

Properties

allocSize

fixed

owned

parent