{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (garetxe@gmail.com)

'GI.GstBase.Structs.ByteWriter.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.
-}

module GI.GstBase.Structs.ByteWriter
    ( 

-- * Exported types
    ByteWriter(..)                          ,
    newZeroByteWriter                       ,
    noByteWriter                            ,


 -- * Methods
-- ** ensureFreeSpace #method:ensureFreeSpace#
    ByteWriterEnsureFreeSpaceMethodInfo     ,
    byteWriterEnsureFreeSpace               ,


-- ** fill #method:fill#
    ByteWriterFillMethodInfo                ,
    byteWriterFill                          ,


-- ** free #method:free#
    ByteWriterFreeMethodInfo                ,
    byteWriterFree                          ,


-- ** freeAndGetBuffer #method:freeAndGetBuffer#
    ByteWriterFreeAndGetBufferMethodInfo    ,
    byteWriterFreeAndGetBuffer              ,


-- ** freeAndGetData #method:freeAndGetData#
    ByteWriterFreeAndGetDataMethodInfo      ,
    byteWriterFreeAndGetData                ,


-- ** getRemaining #method:getRemaining#
    ByteWriterGetRemainingMethodInfo        ,
    byteWriterGetRemaining                  ,


-- ** init #method:init#
    ByteWriterInitMethodInfo                ,
    byteWriterInit                          ,


-- ** initWithData #method:initWithData#
    ByteWriterInitWithDataMethodInfo        ,
    byteWriterInitWithData                  ,


-- ** initWithSize #method:initWithSize#
    ByteWriterInitWithSizeMethodInfo        ,
    byteWriterInitWithSize                  ,


-- ** putBuffer #method:putBuffer#
    ByteWriterPutBufferMethodInfo           ,
    byteWriterPutBuffer                     ,


-- ** putData #method:putData#
    ByteWriterPutDataMethodInfo             ,
    byteWriterPutData                       ,


-- ** putFloat32Be #method:putFloat32Be#
    ByteWriterPutFloat32BeMethodInfo        ,
    byteWriterPutFloat32Be                  ,


-- ** putFloat32Le #method:putFloat32Le#
    ByteWriterPutFloat32LeMethodInfo        ,
    byteWriterPutFloat32Le                  ,


-- ** putFloat64Be #method:putFloat64Be#
    ByteWriterPutFloat64BeMethodInfo        ,
    byteWriterPutFloat64Be                  ,


-- ** putFloat64Le #method:putFloat64Le#
    ByteWriterPutFloat64LeMethodInfo        ,
    byteWriterPutFloat64Le                  ,


-- ** putInt16Be #method:putInt16Be#
    ByteWriterPutInt16BeMethodInfo          ,
    byteWriterPutInt16Be                    ,


-- ** putInt16Le #method:putInt16Le#
    ByteWriterPutInt16LeMethodInfo          ,
    byteWriterPutInt16Le                    ,


-- ** putInt24Be #method:putInt24Be#
    ByteWriterPutInt24BeMethodInfo          ,
    byteWriterPutInt24Be                    ,


-- ** putInt24Le #method:putInt24Le#
    ByteWriterPutInt24LeMethodInfo          ,
    byteWriterPutInt24Le                    ,


-- ** putInt32Be #method:putInt32Be#
    ByteWriterPutInt32BeMethodInfo          ,
    byteWriterPutInt32Be                    ,


-- ** putInt32Le #method:putInt32Le#
    ByteWriterPutInt32LeMethodInfo          ,
    byteWriterPutInt32Le                    ,


-- ** putInt64Be #method:putInt64Be#
    ByteWriterPutInt64BeMethodInfo          ,
    byteWriterPutInt64Be                    ,


-- ** putInt64Le #method:putInt64Le#
    ByteWriterPutInt64LeMethodInfo          ,
    byteWriterPutInt64Le                    ,


-- ** putInt8 #method:putInt8#
    ByteWriterPutInt8MethodInfo             ,
    byteWriterPutInt8                       ,


-- ** putStringUtf16 #method:putStringUtf16#
    ByteWriterPutStringUtf16MethodInfo      ,
    byteWriterPutStringUtf16                ,


-- ** putStringUtf32 #method:putStringUtf32#
    ByteWriterPutStringUtf32MethodInfo      ,
    byteWriterPutStringUtf32                ,


-- ** putStringUtf8 #method:putStringUtf8#
    ByteWriterPutStringUtf8MethodInfo       ,
    byteWriterPutStringUtf8                 ,


-- ** putUint16Be #method:putUint16Be#
    ByteWriterPutUint16BeMethodInfo         ,
    byteWriterPutUint16Be                   ,


-- ** putUint16Le #method:putUint16Le#
    ByteWriterPutUint16LeMethodInfo         ,
    byteWriterPutUint16Le                   ,


-- ** putUint24Be #method:putUint24Be#
    ByteWriterPutUint24BeMethodInfo         ,
    byteWriterPutUint24Be                   ,


-- ** putUint24Le #method:putUint24Le#
    ByteWriterPutUint24LeMethodInfo         ,
    byteWriterPutUint24Le                   ,


-- ** putUint32Be #method:putUint32Be#
    ByteWriterPutUint32BeMethodInfo         ,
    byteWriterPutUint32Be                   ,


-- ** putUint32Le #method:putUint32Le#
    ByteWriterPutUint32LeMethodInfo         ,
    byteWriterPutUint32Le                   ,


-- ** putUint64Be #method:putUint64Be#
    ByteWriterPutUint64BeMethodInfo         ,
    byteWriterPutUint64Be                   ,


-- ** putUint64Le #method:putUint64Le#
    ByteWriterPutUint64LeMethodInfo         ,
    byteWriterPutUint64Le                   ,


-- ** putUint8 #method:putUint8#
    ByteWriterPutUint8MethodInfo            ,
    byteWriterPutUint8                      ,


-- ** reset #method:reset#
    ByteWriterResetMethodInfo               ,
    byteWriterReset                         ,


-- ** resetAndGetBuffer #method:resetAndGetBuffer#
    ByteWriterResetAndGetBufferMethodInfo   ,
    byteWriterResetAndGetBuffer             ,


-- ** resetAndGetData #method:resetAndGetData#
    ByteWriterResetAndGetDataMethodInfo     ,
    byteWriterResetAndGetData               ,




 -- * Properties
-- ** allocSize #attr:allocSize#
    byteWriter_allocSize                    ,
    getByteWriterAllocSize                  ,
    setByteWriterAllocSize                  ,


-- ** fixed #attr:fixed#
    byteWriter_fixed                        ,
    getByteWriterFixed                      ,
    setByteWriterFixed                      ,


-- ** owned #attr:owned#
    byteWriter_owned                        ,
    getByteWriterOwned                      ,
    setByteWriterOwned                      ,


-- ** parent #attr:parent#
    byteWriter_parent                       ,
    getByteWriterParent                     ,




    ) 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.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
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 GI.Gst.Structs.Buffer as Gst.Buffer
import {-# SOURCE #-} qualified GI.GstBase.Structs.ByteReader as GstBase.ByteReader

newtype ByteWriter = ByteWriter (ManagedPtr ByteWriter)
instance WrappedPtr ByteWriter where
    wrappedPtrCalloc = callocBytes 96
    wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 96 >=> wrapPtr ByteWriter)
    wrappedPtrFree = Just ptr_to_g_free

-- | Construct a `ByteWriter` struct initialized to zero.
newZeroByteWriter :: MonadIO m => m ByteWriter
newZeroByteWriter = liftIO $ wrappedPtrCalloc >>= wrapPtr ByteWriter

instance tag ~ 'AttrSet => Constructible ByteWriter tag where
    new _ attrs = do
        o <- newZeroByteWriter
        GI.Attributes.set o attrs
        return o


noByteWriter :: Maybe ByteWriter
noByteWriter = Nothing

getByteWriterParent :: MonadIO m => ByteWriter -> m GstBase.ByteReader.ByteReader
getByteWriterParent s = liftIO $ withManagedPtr s $ \ptr -> do
    let val = ptr `plusPtr` 0 :: (Ptr GstBase.ByteReader.ByteReader)
    val' <- (newPtr GstBase.ByteReader.ByteReader) val
    return val'

data ByteWriterParentFieldInfo
instance AttrInfo ByteWriterParentFieldInfo where
    type AttrAllowedOps ByteWriterParentFieldInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint ByteWriterParentFieldInfo = (~) (Ptr GstBase.ByteReader.ByteReader)
    type AttrBaseTypeConstraint ByteWriterParentFieldInfo = (~) ByteWriter
    type AttrGetType ByteWriterParentFieldInfo = GstBase.ByteReader.ByteReader
    type AttrLabel ByteWriterParentFieldInfo = "parent"
    type AttrOrigin ByteWriterParentFieldInfo = ByteWriter
    attrGet _ = getByteWriterParent
    attrSet _ = undefined
    attrConstruct = undefined
    attrClear _ = undefined

byteWriter_parent :: AttrLabelProxy "parent"
byteWriter_parent = AttrLabelProxy


getByteWriterAllocSize :: MonadIO m => ByteWriter -> m Word32
getByteWriterAllocSize s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 48) :: IO Word32
    return val

setByteWriterAllocSize :: MonadIO m => ByteWriter -> Word32 -> m ()
setByteWriterAllocSize s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 48) (val :: Word32)

data ByteWriterAllocSizeFieldInfo
instance AttrInfo ByteWriterAllocSizeFieldInfo where
    type AttrAllowedOps ByteWriterAllocSizeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ByteWriterAllocSizeFieldInfo = (~) Word32
    type AttrBaseTypeConstraint ByteWriterAllocSizeFieldInfo = (~) ByteWriter
    type AttrGetType ByteWriterAllocSizeFieldInfo = Word32
    type AttrLabel ByteWriterAllocSizeFieldInfo = "alloc_size"
    type AttrOrigin ByteWriterAllocSizeFieldInfo = ByteWriter
    attrGet _ = getByteWriterAllocSize
    attrSet _ = setByteWriterAllocSize
    attrConstruct = undefined
    attrClear _ = undefined

byteWriter_allocSize :: AttrLabelProxy "allocSize"
byteWriter_allocSize = AttrLabelProxy


getByteWriterFixed :: MonadIO m => ByteWriter -> m Bool
getByteWriterFixed s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 52) :: IO CInt
    let val' = (/= 0) val
    return val'

setByteWriterFixed :: MonadIO m => ByteWriter -> Bool -> m ()
setByteWriterFixed s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 52) (val' :: CInt)

data ByteWriterFixedFieldInfo
instance AttrInfo ByteWriterFixedFieldInfo where
    type AttrAllowedOps ByteWriterFixedFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ByteWriterFixedFieldInfo = (~) Bool
    type AttrBaseTypeConstraint ByteWriterFixedFieldInfo = (~) ByteWriter
    type AttrGetType ByteWriterFixedFieldInfo = Bool
    type AttrLabel ByteWriterFixedFieldInfo = "fixed"
    type AttrOrigin ByteWriterFixedFieldInfo = ByteWriter
    attrGet _ = getByteWriterFixed
    attrSet _ = setByteWriterFixed
    attrConstruct = undefined
    attrClear _ = undefined

byteWriter_fixed :: AttrLabelProxy "fixed"
byteWriter_fixed = AttrLabelProxy


getByteWriterOwned :: MonadIO m => ByteWriter -> m Bool
getByteWriterOwned s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 56) :: IO CInt
    let val' = (/= 0) val
    return val'

setByteWriterOwned :: MonadIO m => ByteWriter -> Bool -> m ()
setByteWriterOwned s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 56) (val' :: CInt)

data ByteWriterOwnedFieldInfo
instance AttrInfo ByteWriterOwnedFieldInfo where
    type AttrAllowedOps ByteWriterOwnedFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ByteWriterOwnedFieldInfo = (~) Bool
    type AttrBaseTypeConstraint ByteWriterOwnedFieldInfo = (~) ByteWriter
    type AttrGetType ByteWriterOwnedFieldInfo = Bool
    type AttrLabel ByteWriterOwnedFieldInfo = "owned"
    type AttrOrigin ByteWriterOwnedFieldInfo = ByteWriter
    attrGet _ = getByteWriterOwned
    attrSet _ = setByteWriterOwned
    attrConstruct = undefined
    attrClear _ = undefined

byteWriter_owned :: AttrLabelProxy "owned"
byteWriter_owned = AttrLabelProxy



instance O.HasAttributeList ByteWriter
type instance O.AttributeList ByteWriter = ByteWriterAttributeList
type ByteWriterAttributeList = ('[ '("parent", ByteWriterParentFieldInfo), '("allocSize", ByteWriterAllocSizeFieldInfo), '("fixed", ByteWriterFixedFieldInfo), '("owned", ByteWriterOwnedFieldInfo)] :: [(Symbol, *)])

-- method ByteWriter::ensure_free_space
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "size", argType = TBasicType TUInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Number of bytes that should be available", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_ensure_free_space" gst_byte_writer_ensure_free_space :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    Word32 ->                               -- size : TBasicType TUInt
    IO CInt

{- |
Checks if enough free space from the current write cursor is
available and reallocates if necessary.
-}
byteWriterEnsureFreeSpace ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.ByteWriter' instance -}
    -> Word32
    {- ^ /@size@/: Number of bytes that should be available -}
    -> m Bool
    {- ^ __Returns:__ 'True' if at least /@size@/ bytes are still available -}
byteWriterEnsureFreeSpace writer size = liftIO $ do
    writer' <- unsafeManagedPtrGetPtr writer
    result <- gst_byte_writer_ensure_free_space writer' size
    let result' = (/= 0) result
    touchManagedPtr writer
    return result'

data ByteWriterEnsureFreeSpaceMethodInfo
instance (signature ~ (Word32 -> m Bool), MonadIO m) => O.MethodInfo ByteWriterEnsureFreeSpaceMethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterEnsureFreeSpace

-- method ByteWriter::fill
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "value", argType = TBasicType TUInt8, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Value to be written", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "size", argType = TBasicType TUInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Number of bytes to be written", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_fill" gst_byte_writer_fill :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    Word8 ->                                -- value : TBasicType TUInt8
    Word32 ->                               -- size : TBasicType TUInt
    IO CInt

{- |
Writes /@size@/ bytes containing /@value@/ to /@writer@/.
-}
byteWriterFill ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.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 -}
byteWriterFill writer value size = liftIO $ do
    writer' <- unsafeManagedPtrGetPtr writer
    result <- gst_byte_writer_fill writer' value size
    let result' = (/= 0) result
    touchManagedPtr writer
    return result'

data ByteWriterFillMethodInfo
instance (signature ~ (Word8 -> Word32 -> m Bool), MonadIO m) => O.MethodInfo ByteWriterFillMethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterFill

-- method ByteWriter::free
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_free" gst_byte_writer_free :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    IO ()

{- |
Frees /@writer@/ and all memory allocated by it.
-}
byteWriterFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.ByteWriter' instance -}
    -> m ()
byteWriterFree writer = liftIO $ do
    writer' <- unsafeManagedPtrGetPtr writer
    gst_byte_writer_free writer'
    touchManagedPtr writer
    return ()

data ByteWriterFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo ByteWriterFreeMethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterFree

-- method ByteWriter::free_and_get_buffer
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TInterface (Name {namespace = "Gst", name = "Buffer"}))
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_free_and_get_buffer" gst_byte_writer_free_and_get_buffer :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    IO (Ptr Gst.Buffer.Buffer)

{- |
Frees /@writer@/ and all memory allocated by it except
the current data, which is returned as 'GI.Gst.Structs.Buffer.Buffer'.

Free-function: gst_buffer_unref
-}
byteWriterFreeAndGetBuffer ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.ByteWriter' instance -}
    -> m Gst.Buffer.Buffer
    {- ^ __Returns:__ the current data as buffer. @/gst_buffer_unref()/@
    after usage. -}
byteWriterFreeAndGetBuffer writer = liftIO $ do
    writer' <- unsafeManagedPtrGetPtr writer
    result <- gst_byte_writer_free_and_get_buffer writer'
    checkUnexpectedReturnNULL "byteWriterFreeAndGetBuffer" result
    result' <- (wrapBoxed Gst.Buffer.Buffer) result
    touchManagedPtr writer
    return result'

data ByteWriterFreeAndGetBufferMethodInfo
instance (signature ~ (m Gst.Buffer.Buffer), MonadIO m) => O.MethodInfo ByteWriterFreeAndGetBufferMethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterFreeAndGetBuffer

-- method ByteWriter::free_and_get_data
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TUInt8)
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_free_and_get_data" gst_byte_writer_free_and_get_data :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    IO Word8

{- |
Frees /@writer@/ and all memory allocated by it except
the current data, which is returned.

Free-function: g_free
-}
byteWriterFreeAndGetData ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.ByteWriter' instance -}
    -> m Word8
    {- ^ __Returns:__ the current data. 'GI.GLib.Functions.free' after usage. -}
byteWriterFreeAndGetData writer = liftIO $ do
    writer' <- unsafeManagedPtrGetPtr writer
    result <- gst_byte_writer_free_and_get_data writer'
    touchManagedPtr writer
    return result

data ByteWriterFreeAndGetDataMethodInfo
instance (signature ~ (m Word8), MonadIO m) => O.MethodInfo ByteWriterFreeAndGetDataMethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterFreeAndGetData

-- method ByteWriter::get_remaining
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_get_remaining" gst_byte_writer_get_remaining :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    IO Word32

{- |
Returns the remaining size of data that can still be written. If
-1 is returned the remaining size is only limited by system resources.
-}
byteWriterGetRemaining ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.ByteWriter' instance -}
    -> m Word32
    {- ^ __Returns:__ the remaining size of data that can still be written -}
byteWriterGetRemaining writer = liftIO $ do
    writer' <- unsafeManagedPtrGetPtr writer
    result <- gst_byte_writer_get_remaining writer'
    touchManagedPtr writer
    return result

data ByteWriterGetRemainingMethodInfo
instance (signature ~ (m Word32), MonadIO m) => O.MethodInfo ByteWriterGetRemainingMethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterGetRemaining

-- method ByteWriter::init
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_init" gst_byte_writer_init :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    IO ()

{- |
Initializes /@writer@/ to an empty instance
-}
byteWriterInit ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.ByteWriter' instance -}
    -> m ()
byteWriterInit writer = liftIO $ do
    writer' <- unsafeManagedPtrGetPtr writer
    gst_byte_writer_init writer'
    touchManagedPtr writer
    return ()

data ByteWriterInitMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo ByteWriterInitMethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterInit

-- method ByteWriter::init_with_data
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "data", argType = TCArray False (-1) 2 (TBasicType TUInt8), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Memory area for writing", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "size", argType = TBasicType TUInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Size of @data in bytes", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "initialized", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "If %TRUE the complete data can be read from the beginning", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : [Arg {argCName = "size", argType = TBasicType TUInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Size of @data in bytes", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- returnType : Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_init_with_data" gst_byte_writer_init_with_data :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    Ptr Word8 ->                            -- data : TCArray False (-1) 2 (TBasicType TUInt8)
    Word32 ->                               -- size : TBasicType TUInt
    CInt ->                                 -- initialized : TBasicType TBoolean
    IO ()

{- |
Initializes /@writer@/ with the given
memory area. If /@initialized@/ is 'True' it is possible to
read /@size@/ bytes from the 'GI.GstBase.Structs.ByteWriter.ByteWriter' from the beginning.
-}
byteWriterInitWithData ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.ByteWriter' instance -}
    -> ByteString
    {- ^ /@data@/: Memory area for writing -}
    -> Bool
    {- ^ /@initialized@/: If 'True' the complete data can be read from the beginning -}
    -> m ()
byteWriterInitWithData writer data_ initialized = liftIO $ do
    let size = fromIntegral $ B.length data_
    writer' <- unsafeManagedPtrGetPtr writer
    data_' <- packByteString data_
    let initialized' = (fromIntegral . fromEnum) initialized
    gst_byte_writer_init_with_data writer' data_' size initialized'
    touchManagedPtr writer
    freeMem data_'
    return ()

data ByteWriterInitWithDataMethodInfo
instance (signature ~ (ByteString -> Bool -> m ()), MonadIO m) => O.MethodInfo ByteWriterInitWithDataMethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterInitWithData

-- method ByteWriter::init_with_size
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "size", argType = TBasicType TUInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Initial size of data", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "fixed", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "If %TRUE the data can't be reallocated", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_init_with_size" gst_byte_writer_init_with_size :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    Word32 ->                               -- size : TBasicType TUInt
    CInt ->                                 -- fixed : TBasicType TBoolean
    IO ()

{- |
Initializes /@writer@/ with the given initial data size.
-}
byteWriterInitWithSize ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.ByteWriter' instance -}
    -> Word32
    {- ^ /@size@/: Initial size of data -}
    -> Bool
    {- ^ /@fixed@/: If 'True' the data can\'t be reallocated -}
    -> m ()
byteWriterInitWithSize writer size fixed = liftIO $ do
    writer' <- unsafeManagedPtrGetPtr writer
    let fixed' = (fromIntegral . fromEnum) fixed
    gst_byte_writer_init_with_size writer' size fixed'
    touchManagedPtr writer
    return ()

data ByteWriterInitWithSizeMethodInfo
instance (signature ~ (Word32 -> Bool -> m ()), MonadIO m) => O.MethodInfo ByteWriterInitWithSizeMethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterInitWithSize

-- method ByteWriter::put_buffer
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "buffer", argType = TInterface (Name {namespace = "Gst", name = "Buffer"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "source #GstBuffer", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "offset", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "offset to copy from", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "size", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "total size to copy. If -1, all data is copied", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_put_buffer" gst_byte_writer_put_buffer :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    Ptr Gst.Buffer.Buffer ->                -- buffer : TInterface (Name {namespace = "Gst", name = "Buffer"})
    Word64 ->                               -- offset : TBasicType TUInt64
    Int64 ->                                -- size : TBasicType TInt64
    IO CInt

{- |
Writes /@size@/ bytes of /@data@/ to /@writer@/.
-}
byteWriterPutBuffer ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.ByteWriter' instance -}
    -> Gst.Buffer.Buffer
    {- ^ /@buffer@/: source 'GI.Gst.Structs.Buffer.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 -}
byteWriterPutBuffer writer buffer offset size = liftIO $ do
    writer' <- unsafeManagedPtrGetPtr writer
    buffer' <- unsafeManagedPtrGetPtr buffer
    result <- gst_byte_writer_put_buffer writer' buffer' offset size
    let result' = (/= 0) result
    touchManagedPtr writer
    touchManagedPtr buffer
    return result'

data ByteWriterPutBufferMethodInfo
instance (signature ~ (Gst.Buffer.Buffer -> Word64 -> Int64 -> m Bool), MonadIO m) => O.MethodInfo ByteWriterPutBufferMethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterPutBuffer

-- method ByteWriter::put_data
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "data", argType = TCArray False (-1) 2 (TBasicType TUInt8), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Data to write", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "size", argType = TBasicType TUInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Size of @data in bytes", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : [Arg {argCName = "size", argType = TBasicType TUInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Size of @data in bytes", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_put_data" gst_byte_writer_put_data :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    Ptr Word8 ->                            -- data : TCArray False (-1) 2 (TBasicType TUInt8)
    Word32 ->                               -- size : TBasicType TUInt
    IO CInt

{- |
Writes /@size@/ bytes of /@data@/ to /@writer@/.
-}
byteWriterPutData ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.ByteWriter' instance -}
    -> ByteString
    {- ^ /@data@/: Data to write -}
    -> m Bool
    {- ^ __Returns:__ 'True' if the value could be written -}
byteWriterPutData writer data_ = liftIO $ do
    let size = fromIntegral $ B.length data_
    writer' <- unsafeManagedPtrGetPtr writer
    data_' <- packByteString data_
    result <- gst_byte_writer_put_data writer' data_' size
    let result' = (/= 0) result
    touchManagedPtr writer
    freeMem data_'
    return result'

data ByteWriterPutDataMethodInfo
instance (signature ~ (ByteString -> m Bool), MonadIO m) => O.MethodInfo ByteWriterPutDataMethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterPutData

-- method ByteWriter::put_float32_be
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TFloat, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Value to write", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_put_float32_be" gst_byte_writer_put_float32_be :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    CFloat ->                               -- val : TBasicType TFloat
    IO CInt

{- |
Writes a big endian 32 bit float to /@writer@/.
-}
byteWriterPutFloat32Be ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.ByteWriter' instance -}
    -> Float
    {- ^ /@val@/: Value to write -}
    -> m Bool
    {- ^ __Returns:__ 'True' if the value could be written -}
byteWriterPutFloat32Be writer val = liftIO $ do
    writer' <- unsafeManagedPtrGetPtr writer
    let val' = realToFrac val
    result <- gst_byte_writer_put_float32_be writer' val'
    let result' = (/= 0) result
    touchManagedPtr writer
    return result'

data ByteWriterPutFloat32BeMethodInfo
instance (signature ~ (Float -> m Bool), MonadIO m) => O.MethodInfo ByteWriterPutFloat32BeMethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterPutFloat32Be

-- method ByteWriter::put_float32_le
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TFloat, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Value to write", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_put_float32_le" gst_byte_writer_put_float32_le :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    CFloat ->                               -- val : TBasicType TFloat
    IO CInt

{- |
Writes a little endian 32 bit float to /@writer@/.
-}
byteWriterPutFloat32Le ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.ByteWriter' instance -}
    -> Float
    {- ^ /@val@/: Value to write -}
    -> m Bool
    {- ^ __Returns:__ 'True' if the value could be written -}
byteWriterPutFloat32Le writer val = liftIO $ do
    writer' <- unsafeManagedPtrGetPtr writer
    let val' = realToFrac val
    result <- gst_byte_writer_put_float32_le writer' val'
    let result' = (/= 0) result
    touchManagedPtr writer
    return result'

data ByteWriterPutFloat32LeMethodInfo
instance (signature ~ (Float -> m Bool), MonadIO m) => O.MethodInfo ByteWriterPutFloat32LeMethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterPutFloat32Le

-- method ByteWriter::put_float64_be
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Value to write", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_put_float64_be" gst_byte_writer_put_float64_be :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    CDouble ->                              -- val : TBasicType TDouble
    IO CInt

{- |
Writes a big endian 64 bit float to /@writer@/.
-}
byteWriterPutFloat64Be ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.ByteWriter' instance -}
    -> Double
    {- ^ /@val@/: Value to write -}
    -> m Bool
    {- ^ __Returns:__ 'True' if the value could be written -}
byteWriterPutFloat64Be writer val = liftIO $ do
    writer' <- unsafeManagedPtrGetPtr writer
    let val' = realToFrac val
    result <- gst_byte_writer_put_float64_be writer' val'
    let result' = (/= 0) result
    touchManagedPtr writer
    return result'

data ByteWriterPutFloat64BeMethodInfo
instance (signature ~ (Double -> m Bool), MonadIO m) => O.MethodInfo ByteWriterPutFloat64BeMethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterPutFloat64Be

-- method ByteWriter::put_float64_le
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Value to write", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_put_float64_le" gst_byte_writer_put_float64_le :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    CDouble ->                              -- val : TBasicType TDouble
    IO CInt

{- |
Writes a little endian 64 bit float to /@writer@/.
-}
byteWriterPutFloat64Le ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.ByteWriter' instance -}
    -> Double
    {- ^ /@val@/: Value to write -}
    -> m Bool
    {- ^ __Returns:__ 'True' if the value could be written -}
byteWriterPutFloat64Le writer val = liftIO $ do
    writer' <- unsafeManagedPtrGetPtr writer
    let val' = realToFrac val
    result <- gst_byte_writer_put_float64_le writer' val'
    let result' = (/= 0) result
    touchManagedPtr writer
    return result'

data ByteWriterPutFloat64LeMethodInfo
instance (signature ~ (Double -> m Bool), MonadIO m) => O.MethodInfo ByteWriterPutFloat64LeMethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterPutFloat64Le

-- method ByteWriter::put_int16_be
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TInt16, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Value to write", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_put_int16_be" gst_byte_writer_put_int16_be :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    Int16 ->                                -- val : TBasicType TInt16
    IO CInt

{- |
Writes a signed big endian 16 bit integer to /@writer@/.
-}
byteWriterPutInt16Be ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.ByteWriter' instance -}
    -> Int16
    {- ^ /@val@/: Value to write -}
    -> m Bool
    {- ^ __Returns:__ 'True' if the value could be written -}
byteWriterPutInt16Be writer val = liftIO $ do
    writer' <- unsafeManagedPtrGetPtr writer
    result <- gst_byte_writer_put_int16_be writer' val
    let result' = (/= 0) result
    touchManagedPtr writer
    return result'

data ByteWriterPutInt16BeMethodInfo
instance (signature ~ (Int16 -> m Bool), MonadIO m) => O.MethodInfo ByteWriterPutInt16BeMethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterPutInt16Be

-- method ByteWriter::put_int16_le
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TInt16, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Value to write", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_put_int16_le" gst_byte_writer_put_int16_le :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    Int16 ->                                -- val : TBasicType TInt16
    IO CInt

{- |
Writes a signed little endian 16 bit integer to /@writer@/.
-}
byteWriterPutInt16Le ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.ByteWriter' instance -}
    -> Int16
    {- ^ /@val@/: Value to write -}
    -> m Bool
    {- ^ __Returns:__ 'True' if the value could be written -}
byteWriterPutInt16Le writer val = liftIO $ do
    writer' <- unsafeManagedPtrGetPtr writer
    result <- gst_byte_writer_put_int16_le writer' val
    let result' = (/= 0) result
    touchManagedPtr writer
    return result'

data ByteWriterPutInt16LeMethodInfo
instance (signature ~ (Int16 -> m Bool), MonadIO m) => O.MethodInfo ByteWriterPutInt16LeMethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterPutInt16Le

-- method ByteWriter::put_int24_be
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Value to write", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_put_int24_be" gst_byte_writer_put_int24_be :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    Int32 ->                                -- val : TBasicType TInt32
    IO CInt

{- |
Writes a signed big endian 24 bit integer to /@writer@/.
-}
byteWriterPutInt24Be ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.ByteWriter' instance -}
    -> Int32
    {- ^ /@val@/: Value to write -}
    -> m Bool
    {- ^ __Returns:__ 'True' if the value could be written -}
byteWriterPutInt24Be writer val = liftIO $ do
    writer' <- unsafeManagedPtrGetPtr writer
    result <- gst_byte_writer_put_int24_be writer' val
    let result' = (/= 0) result
    touchManagedPtr writer
    return result'

data ByteWriterPutInt24BeMethodInfo
instance (signature ~ (Int32 -> m Bool), MonadIO m) => O.MethodInfo ByteWriterPutInt24BeMethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterPutInt24Be

-- method ByteWriter::put_int24_le
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Value to write", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_put_int24_le" gst_byte_writer_put_int24_le :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    Int32 ->                                -- val : TBasicType TInt32
    IO CInt

{- |
Writes a signed little endian 24 bit integer to /@writer@/.
-}
byteWriterPutInt24Le ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.ByteWriter' instance -}
    -> Int32
    {- ^ /@val@/: Value to write -}
    -> m Bool
    {- ^ __Returns:__ 'True' if the value could be written -}
byteWriterPutInt24Le writer val = liftIO $ do
    writer' <- unsafeManagedPtrGetPtr writer
    result <- gst_byte_writer_put_int24_le writer' val
    let result' = (/= 0) result
    touchManagedPtr writer
    return result'

data ByteWriterPutInt24LeMethodInfo
instance (signature ~ (Int32 -> m Bool), MonadIO m) => O.MethodInfo ByteWriterPutInt24LeMethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterPutInt24Le

-- method ByteWriter::put_int32_be
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Value to write", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_put_int32_be" gst_byte_writer_put_int32_be :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    Int32 ->                                -- val : TBasicType TInt32
    IO CInt

{- |
Writes a signed big endian 32 bit integer to /@writer@/.
-}
byteWriterPutInt32Be ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.ByteWriter' instance -}
    -> Int32
    {- ^ /@val@/: Value to write -}
    -> m Bool
    {- ^ __Returns:__ 'True' if the value could be written -}
byteWriterPutInt32Be writer val = liftIO $ do
    writer' <- unsafeManagedPtrGetPtr writer
    result <- gst_byte_writer_put_int32_be writer' val
    let result' = (/= 0) result
    touchManagedPtr writer
    return result'

data ByteWriterPutInt32BeMethodInfo
instance (signature ~ (Int32 -> m Bool), MonadIO m) => O.MethodInfo ByteWriterPutInt32BeMethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterPutInt32Be

-- method ByteWriter::put_int32_le
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Value to write", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_put_int32_le" gst_byte_writer_put_int32_le :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    Int32 ->                                -- val : TBasicType TInt32
    IO CInt

{- |
Writes a signed little endian 32 bit integer to /@writer@/.
-}
byteWriterPutInt32Le ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.ByteWriter' instance -}
    -> Int32
    {- ^ /@val@/: Value to write -}
    -> m Bool
    {- ^ __Returns:__ 'True' if the value could be written -}
byteWriterPutInt32Le writer val = liftIO $ do
    writer' <- unsafeManagedPtrGetPtr writer
    result <- gst_byte_writer_put_int32_le writer' val
    let result' = (/= 0) result
    touchManagedPtr writer
    return result'

data ByteWriterPutInt32LeMethodInfo
instance (signature ~ (Int32 -> m Bool), MonadIO m) => O.MethodInfo ByteWriterPutInt32LeMethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterPutInt32Le

-- method ByteWriter::put_int64_be
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Value to write", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_put_int64_be" gst_byte_writer_put_int64_be :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    Int64 ->                                -- val : TBasicType TInt64
    IO CInt

{- |
Writes a signed big endian 64 bit integer to /@writer@/.
-}
byteWriterPutInt64Be ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.ByteWriter' instance -}
    -> Int64
    {- ^ /@val@/: Value to write -}
    -> m Bool
    {- ^ __Returns:__ 'True' if the value could be written -}
byteWriterPutInt64Be writer val = liftIO $ do
    writer' <- unsafeManagedPtrGetPtr writer
    result <- gst_byte_writer_put_int64_be writer' val
    let result' = (/= 0) result
    touchManagedPtr writer
    return result'

data ByteWriterPutInt64BeMethodInfo
instance (signature ~ (Int64 -> m Bool), MonadIO m) => O.MethodInfo ByteWriterPutInt64BeMethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterPutInt64Be

-- method ByteWriter::put_int64_le
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Value to write", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_put_int64_le" gst_byte_writer_put_int64_le :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    Int64 ->                                -- val : TBasicType TInt64
    IO CInt

{- |
Writes a signed little endian 64 bit integer to /@writer@/.
-}
byteWriterPutInt64Le ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.ByteWriter' instance -}
    -> Int64
    {- ^ /@val@/: Value to write -}
    -> m Bool
    {- ^ __Returns:__ 'True' if the value could be written -}
byteWriterPutInt64Le writer val = liftIO $ do
    writer' <- unsafeManagedPtrGetPtr writer
    result <- gst_byte_writer_put_int64_le writer' val
    let result' = (/= 0) result
    touchManagedPtr writer
    return result'

data ByteWriterPutInt64LeMethodInfo
instance (signature ~ (Int64 -> m Bool), MonadIO m) => O.MethodInfo ByteWriterPutInt64LeMethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterPutInt64Le

-- method ByteWriter::put_int8
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TInt8, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Value to write", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_put_int8" gst_byte_writer_put_int8 :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    Int8 ->                                 -- val : TBasicType TInt8
    IO CInt

{- |
Writes a signed 8 bit integer to /@writer@/.
-}
byteWriterPutInt8 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.ByteWriter' instance -}
    -> Int8
    {- ^ /@val@/: Value to write -}
    -> m Bool
    {- ^ __Returns:__ 'True' if the value could be written -}
byteWriterPutInt8 writer val = liftIO $ do
    writer' <- unsafeManagedPtrGetPtr writer
    result <- gst_byte_writer_put_int8 writer' val
    let result' = (/= 0) result
    touchManagedPtr writer
    return result'

data ByteWriterPutInt8MethodInfo
instance (signature ~ (Int8 -> m Bool), MonadIO m) => O.MethodInfo ByteWriterPutInt8MethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterPutInt8

-- method ByteWriter::put_string_utf16
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "data", argType = TCArray True (-1) (-1) (TBasicType TUInt16), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "UTF16 string to write", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_put_string_utf16" gst_byte_writer_put_string_utf16 :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    Ptr Word16 ->                           -- data : TCArray True (-1) (-1) (TBasicType TUInt16)
    IO CInt

{- |
Writes a NUL-terminated UTF16 string to /@writer@/ (including the terminator).
-}
byteWriterPutStringUtf16 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.ByteWriter' instance -}
    -> [Word16]
    {- ^ /@data@/: UTF16 string to write -}
    -> m Bool
    {- ^ __Returns:__ 'True' if the value could be written -}
byteWriterPutStringUtf16 writer data_ = liftIO $ do
    writer' <- unsafeManagedPtrGetPtr writer
    data_' <- packZeroTerminatedStorableArray data_
    result <- gst_byte_writer_put_string_utf16 writer' data_'
    let result' = (/= 0) result
    touchManagedPtr writer
    freeMem data_'
    return result'

data ByteWriterPutStringUtf16MethodInfo
instance (signature ~ ([Word16] -> m Bool), MonadIO m) => O.MethodInfo ByteWriterPutStringUtf16MethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterPutStringUtf16

-- method ByteWriter::put_string_utf32
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "data", argType = TCArray True (-1) (-1) (TBasicType TUInt32), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "UTF32 string to write", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_put_string_utf32" gst_byte_writer_put_string_utf32 :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    Ptr Word32 ->                           -- data : TCArray True (-1) (-1) (TBasicType TUInt32)
    IO CInt

{- |
Writes a NUL-terminated UTF32 string to /@writer@/ (including the terminator).
-}
byteWriterPutStringUtf32 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.ByteWriter' instance -}
    -> [Word32]
    {- ^ /@data@/: UTF32 string to write -}
    -> m Bool
    {- ^ __Returns:__ 'True' if the value could be written -}
byteWriterPutStringUtf32 writer data_ = liftIO $ do
    writer' <- unsafeManagedPtrGetPtr writer
    data_' <- packZeroTerminatedStorableArray data_
    result <- gst_byte_writer_put_string_utf32 writer' data_'
    let result' = (/= 0) result
    touchManagedPtr writer
    freeMem data_'
    return result'

data ByteWriterPutStringUtf32MethodInfo
instance (signature ~ ([Word32] -> m Bool), MonadIO m) => O.MethodInfo ByteWriterPutStringUtf32MethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterPutStringUtf32

-- method ByteWriter::put_string_utf8
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "data", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "UTF8 string to\n    write", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_put_string_utf8" gst_byte_writer_put_string_utf8 :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    Ptr CString ->                          -- data : TCArray True (-1) (-1) (TBasicType TUTF8)
    IO CInt

{- |
Writes a NUL-terminated UTF8 string to /@writer@/ (including the terminator).
-}
byteWriterPutStringUtf8 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.ByteWriter' instance -}
    -> [T.Text]
    {- ^ /@data@/: UTF8 string to
    write -}
    -> m Bool
    {- ^ __Returns:__ 'True' if the value could be written -}
byteWriterPutStringUtf8 writer data_ = liftIO $ do
    writer' <- unsafeManagedPtrGetPtr writer
    data_' <- packZeroTerminatedUTF8CArray data_
    result <- gst_byte_writer_put_string_utf8 writer' data_'
    let result' = (/= 0) result
    touchManagedPtr writer
    mapZeroTerminatedCArray freeMem data_'
    freeMem data_'
    return result'

data ByteWriterPutStringUtf8MethodInfo
instance (signature ~ ([T.Text] -> m Bool), MonadIO m) => O.MethodInfo ByteWriterPutStringUtf8MethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterPutStringUtf8

-- method ByteWriter::put_uint16_be
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TUInt16, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Value to write", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_put_uint16_be" gst_byte_writer_put_uint16_be :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    Word16 ->                               -- val : TBasicType TUInt16
    IO CInt

{- |
Writes a unsigned big endian 16 bit integer to /@writer@/.
-}
byteWriterPutUint16Be ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.ByteWriter' instance -}
    -> Word16
    {- ^ /@val@/: Value to write -}
    -> m Bool
    {- ^ __Returns:__ 'True' if the value could be written -}
byteWriterPutUint16Be writer val = liftIO $ do
    writer' <- unsafeManagedPtrGetPtr writer
    result <- gst_byte_writer_put_uint16_be writer' val
    let result' = (/= 0) result
    touchManagedPtr writer
    return result'

data ByteWriterPutUint16BeMethodInfo
instance (signature ~ (Word16 -> m Bool), MonadIO m) => O.MethodInfo ByteWriterPutUint16BeMethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterPutUint16Be

-- method ByteWriter::put_uint16_le
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TUInt16, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Value to write", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_put_uint16_le" gst_byte_writer_put_uint16_le :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    Word16 ->                               -- val : TBasicType TUInt16
    IO CInt

{- |
Writes a unsigned little endian 16 bit integer to /@writer@/.
-}
byteWriterPutUint16Le ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.ByteWriter' instance -}
    -> Word16
    {- ^ /@val@/: Value to write -}
    -> m Bool
    {- ^ __Returns:__ 'True' if the value could be written -}
byteWriterPutUint16Le writer val = liftIO $ do
    writer' <- unsafeManagedPtrGetPtr writer
    result <- gst_byte_writer_put_uint16_le writer' val
    let result' = (/= 0) result
    touchManagedPtr writer
    return result'

data ByteWriterPutUint16LeMethodInfo
instance (signature ~ (Word16 -> m Bool), MonadIO m) => O.MethodInfo ByteWriterPutUint16LeMethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterPutUint16Le

-- method ByteWriter::put_uint24_be
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Value to write", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_put_uint24_be" gst_byte_writer_put_uint24_be :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    Word32 ->                               -- val : TBasicType TUInt32
    IO CInt

{- |
Writes a unsigned big endian 24 bit integer to /@writer@/.
-}
byteWriterPutUint24Be ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.ByteWriter' instance -}
    -> Word32
    {- ^ /@val@/: Value to write -}
    -> m Bool
    {- ^ __Returns:__ 'True' if the value could be written -}
byteWriterPutUint24Be writer val = liftIO $ do
    writer' <- unsafeManagedPtrGetPtr writer
    result <- gst_byte_writer_put_uint24_be writer' val
    let result' = (/= 0) result
    touchManagedPtr writer
    return result'

data ByteWriterPutUint24BeMethodInfo
instance (signature ~ (Word32 -> m Bool), MonadIO m) => O.MethodInfo ByteWriterPutUint24BeMethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterPutUint24Be

-- method ByteWriter::put_uint24_le
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Value to write", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_put_uint24_le" gst_byte_writer_put_uint24_le :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    Word32 ->                               -- val : TBasicType TUInt32
    IO CInt

{- |
Writes a unsigned little endian 24 bit integer to /@writer@/.
-}
byteWriterPutUint24Le ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.ByteWriter' instance -}
    -> Word32
    {- ^ /@val@/: Value to write -}
    -> m Bool
    {- ^ __Returns:__ 'True' if the value could be written -}
byteWriterPutUint24Le writer val = liftIO $ do
    writer' <- unsafeManagedPtrGetPtr writer
    result <- gst_byte_writer_put_uint24_le writer' val
    let result' = (/= 0) result
    touchManagedPtr writer
    return result'

data ByteWriterPutUint24LeMethodInfo
instance (signature ~ (Word32 -> m Bool), MonadIO m) => O.MethodInfo ByteWriterPutUint24LeMethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterPutUint24Le

-- method ByteWriter::put_uint32_be
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Value to write", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_put_uint32_be" gst_byte_writer_put_uint32_be :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    Word32 ->                               -- val : TBasicType TUInt32
    IO CInt

{- |
Writes a unsigned big endian 32 bit integer to /@writer@/.
-}
byteWriterPutUint32Be ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.ByteWriter' instance -}
    -> Word32
    {- ^ /@val@/: Value to write -}
    -> m Bool
    {- ^ __Returns:__ 'True' if the value could be written -}
byteWriterPutUint32Be writer val = liftIO $ do
    writer' <- unsafeManagedPtrGetPtr writer
    result <- gst_byte_writer_put_uint32_be writer' val
    let result' = (/= 0) result
    touchManagedPtr writer
    return result'

data ByteWriterPutUint32BeMethodInfo
instance (signature ~ (Word32 -> m Bool), MonadIO m) => O.MethodInfo ByteWriterPutUint32BeMethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterPutUint32Be

-- method ByteWriter::put_uint32_le
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Value to write", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_put_uint32_le" gst_byte_writer_put_uint32_le :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    Word32 ->                               -- val : TBasicType TUInt32
    IO CInt

{- |
Writes a unsigned little endian 32 bit integer to /@writer@/.
-}
byteWriterPutUint32Le ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.ByteWriter' instance -}
    -> Word32
    {- ^ /@val@/: Value to write -}
    -> m Bool
    {- ^ __Returns:__ 'True' if the value could be written -}
byteWriterPutUint32Le writer val = liftIO $ do
    writer' <- unsafeManagedPtrGetPtr writer
    result <- gst_byte_writer_put_uint32_le writer' val
    let result' = (/= 0) result
    touchManagedPtr writer
    return result'

data ByteWriterPutUint32LeMethodInfo
instance (signature ~ (Word32 -> m Bool), MonadIO m) => O.MethodInfo ByteWriterPutUint32LeMethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterPutUint32Le

-- method ByteWriter::put_uint64_be
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Value to write", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_put_uint64_be" gst_byte_writer_put_uint64_be :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    Word64 ->                               -- val : TBasicType TUInt64
    IO CInt

{- |
Writes a unsigned big endian 64 bit integer to /@writer@/.
-}
byteWriterPutUint64Be ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.ByteWriter' instance -}
    -> Word64
    {- ^ /@val@/: Value to write -}
    -> m Bool
    {- ^ __Returns:__ 'True' if the value could be written -}
byteWriterPutUint64Be writer val = liftIO $ do
    writer' <- unsafeManagedPtrGetPtr writer
    result <- gst_byte_writer_put_uint64_be writer' val
    let result' = (/= 0) result
    touchManagedPtr writer
    return result'

data ByteWriterPutUint64BeMethodInfo
instance (signature ~ (Word64 -> m Bool), MonadIO m) => O.MethodInfo ByteWriterPutUint64BeMethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterPutUint64Be

-- method ByteWriter::put_uint64_le
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Value to write", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_put_uint64_le" gst_byte_writer_put_uint64_le :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    Word64 ->                               -- val : TBasicType TUInt64
    IO CInt

{- |
Writes a unsigned little endian 64 bit integer to /@writer@/.
-}
byteWriterPutUint64Le ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.ByteWriter' instance -}
    -> Word64
    {- ^ /@val@/: Value to write -}
    -> m Bool
    {- ^ __Returns:__ 'True' if the value could be written -}
byteWriterPutUint64Le writer val = liftIO $ do
    writer' <- unsafeManagedPtrGetPtr writer
    result <- gst_byte_writer_put_uint64_le writer' val
    let result' = (/= 0) result
    touchManagedPtr writer
    return result'

data ByteWriterPutUint64LeMethodInfo
instance (signature ~ (Word64 -> m Bool), MonadIO m) => O.MethodInfo ByteWriterPutUint64LeMethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterPutUint64Le

-- method ByteWriter::put_uint8
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TUInt8, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Value to write", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_put_uint8" gst_byte_writer_put_uint8 :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    Word8 ->                                -- val : TBasicType TUInt8
    IO CInt

{- |
Writes a unsigned 8 bit integer to /@writer@/.
-}
byteWriterPutUint8 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.ByteWriter' instance -}
    -> Word8
    {- ^ /@val@/: Value to write -}
    -> m Bool
    {- ^ __Returns:__ 'True' if the value could be written -}
byteWriterPutUint8 writer val = liftIO $ do
    writer' <- unsafeManagedPtrGetPtr writer
    result <- gst_byte_writer_put_uint8 writer' val
    let result' = (/= 0) result
    touchManagedPtr writer
    return result'

data ByteWriterPutUint8MethodInfo
instance (signature ~ (Word8 -> m Bool), MonadIO m) => O.MethodInfo ByteWriterPutUint8MethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterPutUint8

-- method ByteWriter::reset
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_reset" gst_byte_writer_reset :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    IO ()

{- |
Resets /@writer@/ and frees the data if it\'s
owned by /@writer@/.
-}
byteWriterReset ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.ByteWriter' instance -}
    -> m ()
byteWriterReset writer = liftIO $ do
    writer' <- unsafeManagedPtrGetPtr writer
    gst_byte_writer_reset writer'
    touchManagedPtr writer
    return ()

data ByteWriterResetMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo ByteWriterResetMethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterReset

-- method ByteWriter::reset_and_get_buffer
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TInterface (Name {namespace = "Gst", name = "Buffer"}))
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_reset_and_get_buffer" gst_byte_writer_reset_and_get_buffer :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    IO (Ptr Gst.Buffer.Buffer)

{- |
Resets /@writer@/ and returns the current data as buffer.

Free-function: gst_buffer_unref
-}
byteWriterResetAndGetBuffer ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.ByteWriter' instance -}
    -> m Gst.Buffer.Buffer
    {- ^ __Returns:__ the current data as buffer. @/gst_buffer_unref()/@
    after usage. -}
byteWriterResetAndGetBuffer writer = liftIO $ do
    writer' <- unsafeManagedPtrGetPtr writer
    result <- gst_byte_writer_reset_and_get_buffer writer'
    checkUnexpectedReturnNULL "byteWriterResetAndGetBuffer" result
    result' <- (wrapBoxed Gst.Buffer.Buffer) result
    touchManagedPtr writer
    return result'

data ByteWriterResetAndGetBufferMethodInfo
instance (signature ~ (m Gst.Buffer.Buffer), MonadIO m) => O.MethodInfo ByteWriterResetAndGetBufferMethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterResetAndGetBuffer

-- method ByteWriter::reset_and_get_data
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "writer", argType = TInterface (Name {namespace = "GstBase", name = "ByteWriter"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "#GstByteWriter instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TCArray False (-1) (-1) (TBasicType TUInt8))
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_writer_reset_and_get_data" gst_byte_writer_reset_and_get_data :: 
    Ptr ByteWriter ->                       -- writer : TInterface (Name {namespace = "GstBase", name = "ByteWriter"})
    IO (Ptr Word8)

{- |
Resets /@writer@/ and returns the current data.

Free-function: g_free
-}
byteWriterResetAndGetData ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteWriter
    {- ^ /@writer@/: 'GI.GstBase.Structs.ByteWriter.ByteWriter' instance -}
    -> m (Ptr Word8)
    {- ^ __Returns:__ the current data. 'GI.GLib.Functions.free' after
usage. -}
byteWriterResetAndGetData writer = liftIO $ do
    writer' <- unsafeManagedPtrGetPtr writer
    result <- gst_byte_writer_reset_and_get_data writer'
    checkUnexpectedReturnNULL "byteWriterResetAndGetData" result
    touchManagedPtr writer
    return result

data ByteWriterResetAndGetDataMethodInfo
instance (signature ~ (m (Ptr Word8)), MonadIO m) => O.MethodInfo ByteWriterResetAndGetDataMethodInfo ByteWriter signature where
    overloadedMethod _ = byteWriterResetAndGetData

type family ResolveByteWriterMethod (t :: Symbol) (o :: *) :: * where
    ResolveByteWriterMethod "ensureFreeSpace" o = ByteWriterEnsureFreeSpaceMethodInfo
    ResolveByteWriterMethod "fill" o = ByteWriterFillMethodInfo
    ResolveByteWriterMethod "free" o = ByteWriterFreeMethodInfo
    ResolveByteWriterMethod "freeAndGetBuffer" o = ByteWriterFreeAndGetBufferMethodInfo
    ResolveByteWriterMethod "freeAndGetData" o = ByteWriterFreeAndGetDataMethodInfo
    ResolveByteWriterMethod "init" o = ByteWriterInitMethodInfo
    ResolveByteWriterMethod "initWithData" o = ByteWriterInitWithDataMethodInfo
    ResolveByteWriterMethod "initWithSize" o = ByteWriterInitWithSizeMethodInfo
    ResolveByteWriterMethod "putBuffer" o = ByteWriterPutBufferMethodInfo
    ResolveByteWriterMethod "putData" o = ByteWriterPutDataMethodInfo
    ResolveByteWriterMethod "putFloat32Be" o = ByteWriterPutFloat32BeMethodInfo
    ResolveByteWriterMethod "putFloat32Le" o = ByteWriterPutFloat32LeMethodInfo
    ResolveByteWriterMethod "putFloat64Be" o = ByteWriterPutFloat64BeMethodInfo
    ResolveByteWriterMethod "putFloat64Le" o = ByteWriterPutFloat64LeMethodInfo
    ResolveByteWriterMethod "putInt16Be" o = ByteWriterPutInt16BeMethodInfo
    ResolveByteWriterMethod "putInt16Le" o = ByteWriterPutInt16LeMethodInfo
    ResolveByteWriterMethod "putInt24Be" o = ByteWriterPutInt24BeMethodInfo
    ResolveByteWriterMethod "putInt24Le" o = ByteWriterPutInt24LeMethodInfo
    ResolveByteWriterMethod "putInt32Be" o = ByteWriterPutInt32BeMethodInfo
    ResolveByteWriterMethod "putInt32Le" o = ByteWriterPutInt32LeMethodInfo
    ResolveByteWriterMethod "putInt64Be" o = ByteWriterPutInt64BeMethodInfo
    ResolveByteWriterMethod "putInt64Le" o = ByteWriterPutInt64LeMethodInfo
    ResolveByteWriterMethod "putInt8" o = ByteWriterPutInt8MethodInfo
    ResolveByteWriterMethod "putStringUtf16" o = ByteWriterPutStringUtf16MethodInfo
    ResolveByteWriterMethod "putStringUtf32" o = ByteWriterPutStringUtf32MethodInfo
    ResolveByteWriterMethod "putStringUtf8" o = ByteWriterPutStringUtf8MethodInfo
    ResolveByteWriterMethod "putUint16Be" o = ByteWriterPutUint16BeMethodInfo
    ResolveByteWriterMethod "putUint16Le" o = ByteWriterPutUint16LeMethodInfo
    ResolveByteWriterMethod "putUint24Be" o = ByteWriterPutUint24BeMethodInfo
    ResolveByteWriterMethod "putUint24Le" o = ByteWriterPutUint24LeMethodInfo
    ResolveByteWriterMethod "putUint32Be" o = ByteWriterPutUint32BeMethodInfo
    ResolveByteWriterMethod "putUint32Le" o = ByteWriterPutUint32LeMethodInfo
    ResolveByteWriterMethod "putUint64Be" o = ByteWriterPutUint64BeMethodInfo
    ResolveByteWriterMethod "putUint64Le" o = ByteWriterPutUint64LeMethodInfo
    ResolveByteWriterMethod "putUint8" o = ByteWriterPutUint8MethodInfo
    ResolveByteWriterMethod "reset" o = ByteWriterResetMethodInfo
    ResolveByteWriterMethod "resetAndGetBuffer" o = ByteWriterResetAndGetBufferMethodInfo
    ResolveByteWriterMethod "resetAndGetData" o = ByteWriterResetAndGetDataMethodInfo
    ResolveByteWriterMethod "getRemaining" o = ByteWriterGetRemainingMethodInfo
    ResolveByteWriterMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveByteWriterMethod t ByteWriter, O.MethodInfo info ByteWriter p) => O.IsLabelProxy t (ByteWriter -> p) where
    fromLabelProxy _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)

#if MIN_VERSION_base(4,9,0)
instance (info ~ ResolveByteWriterMethod t ByteWriter, O.MethodInfo info ByteWriter p) => O.IsLabel t (ByteWriter -> p) where
    fromLabel _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#endif