{- |
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.ByteReader.ByteReader' provides a byte reader that can read different integer and
floating point types from a memory buffer. It provides functions for 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 read NUL-terminated strings
in various character encodings.
-}

module GI.GstBase.Structs.ByteReader
    ( 

-- * Exported types
    ByteReader(..)                          ,
    newZeroByteReader                       ,
    noByteReader                            ,


 -- * Methods
-- ** dupData #method:dupData#
    ByteReaderDupDataMethodInfo             ,
    byteReaderDupData                       ,


-- ** dupStringUtf16 #method:dupStringUtf16#
    ByteReaderDupStringUtf16MethodInfo      ,
    byteReaderDupStringUtf16                ,


-- ** dupStringUtf32 #method:dupStringUtf32#
    ByteReaderDupStringUtf32MethodInfo      ,
    byteReaderDupStringUtf32                ,


-- ** dupStringUtf8 #method:dupStringUtf8#
    ByteReaderDupStringUtf8MethodInfo       ,
    byteReaderDupStringUtf8                 ,


-- ** free #method:free#
    ByteReaderFreeMethodInfo                ,
    byteReaderFree                          ,


-- ** getData #method:getData#
    ByteReaderGetDataMethodInfo             ,
    byteReaderGetData                       ,


-- ** getFloat32Be #method:getFloat32Be#
    ByteReaderGetFloat32BeMethodInfo        ,
    byteReaderGetFloat32Be                  ,


-- ** getFloat32Le #method:getFloat32Le#
    ByteReaderGetFloat32LeMethodInfo        ,
    byteReaderGetFloat32Le                  ,


-- ** getFloat64Be #method:getFloat64Be#
    ByteReaderGetFloat64BeMethodInfo        ,
    byteReaderGetFloat64Be                  ,


-- ** getFloat64Le #method:getFloat64Le#
    ByteReaderGetFloat64LeMethodInfo        ,
    byteReaderGetFloat64Le                  ,


-- ** getInt16Be #method:getInt16Be#
    ByteReaderGetInt16BeMethodInfo          ,
    byteReaderGetInt16Be                    ,


-- ** getInt16Le #method:getInt16Le#
    ByteReaderGetInt16LeMethodInfo          ,
    byteReaderGetInt16Le                    ,


-- ** getInt24Be #method:getInt24Be#
    ByteReaderGetInt24BeMethodInfo          ,
    byteReaderGetInt24Be                    ,


-- ** getInt24Le #method:getInt24Le#
    ByteReaderGetInt24LeMethodInfo          ,
    byteReaderGetInt24Le                    ,


-- ** getInt32Be #method:getInt32Be#
    ByteReaderGetInt32BeMethodInfo          ,
    byteReaderGetInt32Be                    ,


-- ** getInt32Le #method:getInt32Le#
    ByteReaderGetInt32LeMethodInfo          ,
    byteReaderGetInt32Le                    ,


-- ** getInt64Be #method:getInt64Be#
    ByteReaderGetInt64BeMethodInfo          ,
    byteReaderGetInt64Be                    ,


-- ** getInt64Le #method:getInt64Le#
    ByteReaderGetInt64LeMethodInfo          ,
    byteReaderGetInt64Le                    ,


-- ** getInt8 #method:getInt8#
    ByteReaderGetInt8MethodInfo             ,
    byteReaderGetInt8                       ,


-- ** getPos #method:getPos#
    ByteReaderGetPosMethodInfo              ,
    byteReaderGetPos                        ,


-- ** getRemaining #method:getRemaining#
    ByteReaderGetRemainingMethodInfo        ,
    byteReaderGetRemaining                  ,


-- ** getSize #method:getSize#
    ByteReaderGetSizeMethodInfo             ,
    byteReaderGetSize                       ,


-- ** getStringUtf8 #method:getStringUtf8#
    ByteReaderGetStringUtf8MethodInfo       ,
    byteReaderGetStringUtf8                 ,


-- ** getUint16Be #method:getUint16Be#
    ByteReaderGetUint16BeMethodInfo         ,
    byteReaderGetUint16Be                   ,


-- ** getUint16Le #method:getUint16Le#
    ByteReaderGetUint16LeMethodInfo         ,
    byteReaderGetUint16Le                   ,


-- ** getUint24Be #method:getUint24Be#
    ByteReaderGetUint24BeMethodInfo         ,
    byteReaderGetUint24Be                   ,


-- ** getUint24Le #method:getUint24Le#
    ByteReaderGetUint24LeMethodInfo         ,
    byteReaderGetUint24Le                   ,


-- ** getUint32Be #method:getUint32Be#
    ByteReaderGetUint32BeMethodInfo         ,
    byteReaderGetUint32Be                   ,


-- ** getUint32Le #method:getUint32Le#
    ByteReaderGetUint32LeMethodInfo         ,
    byteReaderGetUint32Le                   ,


-- ** getUint64Be #method:getUint64Be#
    ByteReaderGetUint64BeMethodInfo         ,
    byteReaderGetUint64Be                   ,


-- ** getUint64Le #method:getUint64Le#
    ByteReaderGetUint64LeMethodInfo         ,
    byteReaderGetUint64Le                   ,


-- ** getUint8 #method:getUint8#
    ByteReaderGetUint8MethodInfo            ,
    byteReaderGetUint8                      ,


-- ** init #method:init#
    ByteReaderInitMethodInfo                ,
    byteReaderInit                          ,


-- ** maskedScanUint32 #method:maskedScanUint32#
    ByteReaderMaskedScanUint32MethodInfo    ,
    byteReaderMaskedScanUint32              ,


-- ** maskedScanUint32Peek #method:maskedScanUint32Peek#
    ByteReaderMaskedScanUint32PeekMethodInfo,
    byteReaderMaskedScanUint32Peek          ,


-- ** peekData #method:peekData#
    ByteReaderPeekDataMethodInfo            ,
    byteReaderPeekData                      ,


-- ** peekFloat32Be #method:peekFloat32Be#
    ByteReaderPeekFloat32BeMethodInfo       ,
    byteReaderPeekFloat32Be                 ,


-- ** peekFloat32Le #method:peekFloat32Le#
    ByteReaderPeekFloat32LeMethodInfo       ,
    byteReaderPeekFloat32Le                 ,


-- ** peekFloat64Be #method:peekFloat64Be#
    ByteReaderPeekFloat64BeMethodInfo       ,
    byteReaderPeekFloat64Be                 ,


-- ** peekFloat64Le #method:peekFloat64Le#
    ByteReaderPeekFloat64LeMethodInfo       ,
    byteReaderPeekFloat64Le                 ,


-- ** peekInt16Be #method:peekInt16Be#
    ByteReaderPeekInt16BeMethodInfo         ,
    byteReaderPeekInt16Be                   ,


-- ** peekInt16Le #method:peekInt16Le#
    ByteReaderPeekInt16LeMethodInfo         ,
    byteReaderPeekInt16Le                   ,


-- ** peekInt24Be #method:peekInt24Be#
    ByteReaderPeekInt24BeMethodInfo         ,
    byteReaderPeekInt24Be                   ,


-- ** peekInt24Le #method:peekInt24Le#
    ByteReaderPeekInt24LeMethodInfo         ,
    byteReaderPeekInt24Le                   ,


-- ** peekInt32Be #method:peekInt32Be#
    ByteReaderPeekInt32BeMethodInfo         ,
    byteReaderPeekInt32Be                   ,


-- ** peekInt32Le #method:peekInt32Le#
    ByteReaderPeekInt32LeMethodInfo         ,
    byteReaderPeekInt32Le                   ,


-- ** peekInt64Be #method:peekInt64Be#
    ByteReaderPeekInt64BeMethodInfo         ,
    byteReaderPeekInt64Be                   ,


-- ** peekInt64Le #method:peekInt64Le#
    ByteReaderPeekInt64LeMethodInfo         ,
    byteReaderPeekInt64Le                   ,


-- ** peekInt8 #method:peekInt8#
    ByteReaderPeekInt8MethodInfo            ,
    byteReaderPeekInt8                      ,


-- ** peekStringUtf8 #method:peekStringUtf8#
    ByteReaderPeekStringUtf8MethodInfo      ,
    byteReaderPeekStringUtf8                ,


-- ** peekUint16Be #method:peekUint16Be#
    ByteReaderPeekUint16BeMethodInfo        ,
    byteReaderPeekUint16Be                  ,


-- ** peekUint16Le #method:peekUint16Le#
    ByteReaderPeekUint16LeMethodInfo        ,
    byteReaderPeekUint16Le                  ,


-- ** peekUint24Be #method:peekUint24Be#
    ByteReaderPeekUint24BeMethodInfo        ,
    byteReaderPeekUint24Be                  ,


-- ** peekUint24Le #method:peekUint24Le#
    ByteReaderPeekUint24LeMethodInfo        ,
    byteReaderPeekUint24Le                  ,


-- ** peekUint32Be #method:peekUint32Be#
    ByteReaderPeekUint32BeMethodInfo        ,
    byteReaderPeekUint32Be                  ,


-- ** peekUint32Le #method:peekUint32Le#
    ByteReaderPeekUint32LeMethodInfo        ,
    byteReaderPeekUint32Le                  ,


-- ** peekUint64Be #method:peekUint64Be#
    ByteReaderPeekUint64BeMethodInfo        ,
    byteReaderPeekUint64Be                  ,


-- ** peekUint64Le #method:peekUint64Le#
    ByteReaderPeekUint64LeMethodInfo        ,
    byteReaderPeekUint64Le                  ,


-- ** peekUint8 #method:peekUint8#
    ByteReaderPeekUint8MethodInfo           ,
    byteReaderPeekUint8                     ,


-- ** setPos #method:setPos#
    ByteReaderSetPosMethodInfo              ,
    byteReaderSetPos                        ,


-- ** skip #method:skip#
    ByteReaderSkipMethodInfo                ,
    byteReaderSkip                          ,


-- ** skipStringUtf16 #method:skipStringUtf16#
    ByteReaderSkipStringUtf16MethodInfo     ,
    byteReaderSkipStringUtf16               ,


-- ** skipStringUtf32 #method:skipStringUtf32#
    ByteReaderSkipStringUtf32MethodInfo     ,
    byteReaderSkipStringUtf32               ,


-- ** skipStringUtf8 #method:skipStringUtf8#
    ByteReaderSkipStringUtf8MethodInfo      ,
    byteReaderSkipStringUtf8                ,




 -- * Properties
-- ** byte #attr:byte#
    byteReader_byte                         ,
    getByteReaderByte                       ,
    setByteReaderByte                       ,


-- ** size #attr:size#
    byteReader_size                         ,
    getByteReaderSize                       ,
    setByteReaderSize                       ,




    ) 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


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

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

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


noByteReader :: Maybe ByteReader
noByteReader = Nothing

-- XXX Skipped attribute for "ByteReader:data" :: Not implemented: "Don't know how to unpack C array of type TCArray False (-1) 1 (TBasicType TUInt8)"
getByteReaderSize :: MonadIO m => ByteReader -> m Word32
getByteReaderSize s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO Word32
    return val

setByteReaderSize :: MonadIO m => ByteReader -> Word32 -> m ()
setByteReaderSize s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (val :: Word32)

data ByteReaderSizeFieldInfo
instance AttrInfo ByteReaderSizeFieldInfo where
    type AttrAllowedOps ByteReaderSizeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ByteReaderSizeFieldInfo = (~) Word32
    type AttrBaseTypeConstraint ByteReaderSizeFieldInfo = (~) ByteReader
    type AttrGetType ByteReaderSizeFieldInfo = Word32
    type AttrLabel ByteReaderSizeFieldInfo = "size"
    type AttrOrigin ByteReaderSizeFieldInfo = ByteReader
    attrGet _ = getByteReaderSize
    attrSet _ = setByteReaderSize
    attrConstruct = undefined
    attrClear _ = undefined

byteReader_size :: AttrLabelProxy "size"
byteReader_size = AttrLabelProxy


getByteReaderByte :: MonadIO m => ByteReader -> m Word32
getByteReaderByte s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 12) :: IO Word32
    return val

setByteReaderByte :: MonadIO m => ByteReader -> Word32 -> m ()
setByteReaderByte s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 12) (val :: Word32)

data ByteReaderByteFieldInfo
instance AttrInfo ByteReaderByteFieldInfo where
    type AttrAllowedOps ByteReaderByteFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ByteReaderByteFieldInfo = (~) Word32
    type AttrBaseTypeConstraint ByteReaderByteFieldInfo = (~) ByteReader
    type AttrGetType ByteReaderByteFieldInfo = Word32
    type AttrLabel ByteReaderByteFieldInfo = "byte"
    type AttrOrigin ByteReaderByteFieldInfo = ByteReader
    attrGet _ = getByteReaderByte
    attrSet _ = setByteReaderByte
    attrConstruct = undefined
    attrClear _ = undefined

byteReader_byte :: AttrLabelProxy "byte"
byteReader_byte = AttrLabelProxy



instance O.HasAttributeList ByteReader
type instance O.AttributeList ByteReader = ByteReaderAttributeList
type ByteReaderAttributeList = ('[ '("size", ByteReaderSizeFieldInfo), '("byte", ByteReaderByteFieldInfo)] :: [(Symbol, *)])

-- method ByteReader::dup_data
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "size", argType = TBasicType TUInt, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Size in bytes", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything},Arg {argCName = "val", argType = TCArray False (-1) 1 (TBasicType TUInt8), direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "address of a\n    #guint8 pointer variable in which to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : [Arg {argCName = "size", argType = TBasicType TUInt, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Size in bytes", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_reader_dup_data" gst_byte_reader_dup_data :: 
    Ptr ByteReader ->                       -- reader : TInterface (Name {namespace = "GstBase", name = "ByteReader"})
    Ptr Word32 ->                           -- size : TBasicType TUInt
    Ptr (Ptr Word8) ->                      -- val : TCArray False (-1) 1 (TBasicType TUInt8)
    IO CInt

{- |
Free-function: g_free

Returns a newly-allocated copy of the current data
position if at least /@size@/ bytes are left and
updates the current position. Free with 'GI.GLib.Functions.free' when no longer needed.
-}
byteReaderDupData ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,ByteString)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderDupData reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    size <- allocMem :: IO (Ptr Word32)
    val <- allocMem :: IO (Ptr (Ptr Word8))
    result <- gst_byte_reader_dup_data reader' size val
    size' <- peek size
    let result' = (/= 0) result
    val' <- peek val
    val'' <- (unpackByteStringWithLength size') val'
    freeMem val'
    touchManagedPtr reader
    freeMem size
    freeMem val
    return (result', val'')

data ByteReaderDupDataMethodInfo
instance (signature ~ (m (Bool,ByteString)), MonadIO m) => O.MethodInfo ByteReaderDupDataMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderDupData

-- method ByteReader::dup_string_utf16
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "str", argType = TCArray True (-1) (-1) (TBasicType TUInt16), direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "address of a\n    #guint16 pointer variable in which to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_reader_dup_string_utf16" gst_byte_reader_dup_string_utf16 :: 
    Ptr ByteReader ->                       -- reader : TInterface (Name {namespace = "GstBase", name = "ByteReader"})
    Ptr (Ptr Word16) ->                     -- str : TCArray True (-1) (-1) (TBasicType TUInt16)
    IO CInt

{- |
Free-function: g_free

Returns a newly-allocated copy of the current data position if there is
a NUL-terminated UTF-16 string in the data (this could be an empty string
as well), and advances the current position.

No input checking for valid UTF-16 is done. This function is endianness
agnostic - you should not assume the UTF-16 characters are in host
endianness.

This function will fail if no NUL-terminator was found in in the data.

Note: there is no peek or get variant of this function to ensure correct
byte alignment of the UTF-16 string.
-}
byteReaderDupStringUtf16 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,[Word16])
    {- ^ __Returns:__ 'True' if a string could be read, 'False' otherwise. The
    string put into /@str@/ must be freed with 'GI.GLib.Functions.free' when no longer needed. -}
byteReaderDupStringUtf16 reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    str <- allocMem :: IO (Ptr (Ptr Word16))
    result <- gst_byte_reader_dup_string_utf16 reader' str
    let result' = (/= 0) result
    str' <- peek str
    str'' <- unpackZeroTerminatedStorableArray str'
    freeMem str'
    touchManagedPtr reader
    freeMem str
    return (result', str'')

data ByteReaderDupStringUtf16MethodInfo
instance (signature ~ (m (Bool,[Word16])), MonadIO m) => O.MethodInfo ByteReaderDupStringUtf16MethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderDupStringUtf16

-- method ByteReader::dup_string_utf32
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "str", argType = TCArray True (-1) (-1) (TBasicType TUInt32), direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "address of a\n    #guint32 pointer variable in which to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_reader_dup_string_utf32" gst_byte_reader_dup_string_utf32 :: 
    Ptr ByteReader ->                       -- reader : TInterface (Name {namespace = "GstBase", name = "ByteReader"})
    Ptr (Ptr Word32) ->                     -- str : TCArray True (-1) (-1) (TBasicType TUInt32)
    IO CInt

{- |
Free-function: g_free

Returns a newly-allocated copy of the current data position if there is
a NUL-terminated UTF-32 string in the data (this could be an empty string
as well), and advances the current position.

No input checking for valid UTF-32 is done. This function is endianness
agnostic - you should not assume the UTF-32 characters are in host
endianness.

This function will fail if no NUL-terminator was found in in the data.

Note: there is no peek or get variant of this function to ensure correct
byte alignment of the UTF-32 string.
-}
byteReaderDupStringUtf32 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,[Word32])
    {- ^ __Returns:__ 'True' if a string could be read, 'False' otherwise. The
    string put into /@str@/ must be freed with 'GI.GLib.Functions.free' when no longer needed. -}
byteReaderDupStringUtf32 reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    str <- allocMem :: IO (Ptr (Ptr Word32))
    result <- gst_byte_reader_dup_string_utf32 reader' str
    let result' = (/= 0) result
    str' <- peek str
    str'' <- unpackZeroTerminatedStorableArray str'
    freeMem str'
    touchManagedPtr reader
    freeMem str
    return (result', str'')

data ByteReaderDupStringUtf32MethodInfo
instance (signature ~ (m (Bool,[Word32])), MonadIO m) => O.MethodInfo ByteReaderDupStringUtf32MethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderDupStringUtf32

-- method ByteReader::dup_string_utf8
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "str", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "address of a\n    #gchar pointer variable in which to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_reader_dup_string_utf8" gst_byte_reader_dup_string_utf8 :: 
    Ptr ByteReader ->                       -- reader : TInterface (Name {namespace = "GstBase", name = "ByteReader"})
    Ptr (Ptr CString) ->                    -- str : TCArray True (-1) (-1) (TBasicType TUTF8)
    IO CInt

{- |
Free-function: g_free

FIXME:Reads (copies) a NUL-terminated string in the 'GI.GstBase.Structs.ByteReader.ByteReader' instance,
advancing the current position to the byte after the string. This will work
for any NUL-terminated string with a character width of 8 bits, so ASCII,
UTF-8, ISO-8859-N etc. No input checking for valid UTF-8 is done.

This function will fail if no NUL-terminator was found in in the data.
-}
byteReaderDupStringUtf8 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,[T.Text])
    {- ^ __Returns:__ 'True' if a string could be read into /@str@/, 'False' otherwise. The
    string put into /@str@/ must be freed with 'GI.GLib.Functions.free' when no longer needed. -}
byteReaderDupStringUtf8 reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    str <- allocMem :: IO (Ptr (Ptr CString))
    result <- gst_byte_reader_dup_string_utf8 reader' str
    let result' = (/= 0) result
    str' <- peek str
    str'' <- unpackZeroTerminatedUTF8CArray str'
    mapZeroTerminatedCArray freeMem str'
    freeMem str'
    touchManagedPtr reader
    freeMem str
    return (result', str'')

data ByteReaderDupStringUtf8MethodInfo
instance (signature ~ (m (Bool,[T.Text])), MonadIO m) => O.MethodInfo ByteReaderDupStringUtf8MethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderDupStringUtf8

-- method ByteReader::free
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader 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_reader_free" gst_byte_reader_free :: 
    Ptr ByteReader ->                       -- reader : TInterface (Name {namespace = "GstBase", name = "ByteReader"})
    IO ()

{- |
Frees a 'GI.GstBase.Structs.ByteReader.ByteReader' instance, which was previously allocated by
@/gst_byte_reader_new()/@.
-}
byteReaderFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m ()
byteReaderFree reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    gst_byte_reader_free reader'
    touchManagedPtr reader
    return ()

data ByteReaderFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo ByteReaderFreeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderFree

-- method ByteReader::get_data
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "size", argType = TBasicType TUInt, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Size in bytes", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything},Arg {argCName = "val", argType = TCArray False (-1) 1 (TBasicType TUInt8), direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "address of a\n    #guint8 pointer variable in which to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : [Arg {argCName = "size", argType = TBasicType TUInt, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Size in bytes", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_reader_get_data" gst_byte_reader_get_data :: 
    Ptr ByteReader ->                       -- reader : TInterface (Name {namespace = "GstBase", name = "ByteReader"})
    Ptr Word32 ->                           -- size : TBasicType TUInt
    Ptr (Ptr Word8) ->                      -- val : TCArray False (-1) 1 (TBasicType TUInt8)
    IO CInt

{- |
Returns a constant pointer to the current data
position if at least /@size@/ bytes are left and
updates the current position.
-}
byteReaderGetData ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,ByteString)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderGetData reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    size <- allocMem :: IO (Ptr Word32)
    val <- allocMem :: IO (Ptr (Ptr Word8))
    result <- gst_byte_reader_get_data reader' size val
    size' <- peek size
    let result' = (/= 0) result
    val' <- peek val
    val'' <- (unpackByteStringWithLength size') val'
    touchManagedPtr reader
    freeMem size
    freeMem val
    return (result', val'')

data ByteReaderGetDataMethodInfo
instance (signature ~ (m (Bool,ByteString)), MonadIO m) => O.MethodInfo ByteReaderGetDataMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderGetData

-- method ByteReader::get_float32_be
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TFloat, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #gfloat to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read a 32 bit big endian floating point value into /@val@/
and update the current position.
-}
byteReaderGetFloat32Be ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Float)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderGetFloat32Be reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr CFloat)
    result <- gst_byte_reader_get_float32_be reader' val
    let result' = (/= 0) result
    val' <- peek val
    let val'' = realToFrac val'
    touchManagedPtr reader
    freeMem val
    return (result', val'')

data ByteReaderGetFloat32BeMethodInfo
instance (signature ~ (m (Bool,Float)), MonadIO m) => O.MethodInfo ByteReaderGetFloat32BeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderGetFloat32Be

-- method ByteReader::get_float32_le
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TFloat, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #gfloat to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read a 32 bit little endian floating point value into /@val@/
and update the current position.
-}
byteReaderGetFloat32Le ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Float)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderGetFloat32Le reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr CFloat)
    result <- gst_byte_reader_get_float32_le reader' val
    let result' = (/= 0) result
    val' <- peek val
    let val'' = realToFrac val'
    touchManagedPtr reader
    freeMem val
    return (result', val'')

data ByteReaderGetFloat32LeMethodInfo
instance (signature ~ (m (Bool,Float)), MonadIO m) => O.MethodInfo ByteReaderGetFloat32LeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderGetFloat32Le

-- method ByteReader::get_float64_be
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TDouble, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #gdouble to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read a 64 bit big endian floating point value into /@val@/
and update the current position.
-}
byteReaderGetFloat64Be ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Double)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderGetFloat64Be reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr CDouble)
    result <- gst_byte_reader_get_float64_be reader' val
    let result' = (/= 0) result
    val' <- peek val
    let val'' = realToFrac val'
    touchManagedPtr reader
    freeMem val
    return (result', val'')

data ByteReaderGetFloat64BeMethodInfo
instance (signature ~ (m (Bool,Double)), MonadIO m) => O.MethodInfo ByteReaderGetFloat64BeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderGetFloat64Be

-- method ByteReader::get_float64_le
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TDouble, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #gdouble to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read a 64 bit little endian floating point value into /@val@/
and update the current position.
-}
byteReaderGetFloat64Le ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Double)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderGetFloat64Le reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr CDouble)
    result <- gst_byte_reader_get_float64_le reader' val
    let result' = (/= 0) result
    val' <- peek val
    let val'' = realToFrac val'
    touchManagedPtr reader
    freeMem val
    return (result', val'')

data ByteReaderGetFloat64LeMethodInfo
instance (signature ~ (m (Bool,Double)), MonadIO m) => O.MethodInfo ByteReaderGetFloat64LeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderGetFloat64Le

-- method ByteReader::get_int16_be
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TInt16, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #gint16 to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read a signed 16 bit big endian integer into /@val@/
and update the current position.
-}
byteReaderGetInt16Be ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Int16)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderGetInt16Be reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr Int16)
    result <- gst_byte_reader_get_int16_be reader' val
    let result' = (/= 0) result
    val' <- peek val
    touchManagedPtr reader
    freeMem val
    return (result', val')

data ByteReaderGetInt16BeMethodInfo
instance (signature ~ (m (Bool,Int16)), MonadIO m) => O.MethodInfo ByteReaderGetInt16BeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderGetInt16Be

-- method ByteReader::get_int16_le
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TInt16, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #gint16 to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read a signed 16 bit little endian integer into /@val@/
and update the current position.
-}
byteReaderGetInt16Le ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Int16)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderGetInt16Le reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr Int16)
    result <- gst_byte_reader_get_int16_le reader' val
    let result' = (/= 0) result
    val' <- peek val
    touchManagedPtr reader
    freeMem val
    return (result', val')

data ByteReaderGetInt16LeMethodInfo
instance (signature ~ (m (Bool,Int16)), MonadIO m) => O.MethodInfo ByteReaderGetInt16LeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderGetInt16Le

-- method ByteReader::get_int24_be
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #gint32 to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read a signed 24 bit big endian integer into /@val@/
and update the current position.
-}
byteReaderGetInt24Be ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Int32)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderGetInt24Be reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr Int32)
    result <- gst_byte_reader_get_int24_be reader' val
    let result' = (/= 0) result
    val' <- peek val
    touchManagedPtr reader
    freeMem val
    return (result', val')

data ByteReaderGetInt24BeMethodInfo
instance (signature ~ (m (Bool,Int32)), MonadIO m) => O.MethodInfo ByteReaderGetInt24BeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderGetInt24Be

-- method ByteReader::get_int24_le
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #gint32 to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read a signed 24 bit little endian integer into /@val@/
and update the current position.
-}
byteReaderGetInt24Le ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Int32)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderGetInt24Le reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr Int32)
    result <- gst_byte_reader_get_int24_le reader' val
    let result' = (/= 0) result
    val' <- peek val
    touchManagedPtr reader
    freeMem val
    return (result', val')

data ByteReaderGetInt24LeMethodInfo
instance (signature ~ (m (Bool,Int32)), MonadIO m) => O.MethodInfo ByteReaderGetInt24LeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderGetInt24Le

-- method ByteReader::get_int32_be
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #gint32 to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read a signed 32 bit big endian integer into /@val@/
and update the current position.
-}
byteReaderGetInt32Be ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Int32)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderGetInt32Be reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr Int32)
    result <- gst_byte_reader_get_int32_be reader' val
    let result' = (/= 0) result
    val' <- peek val
    touchManagedPtr reader
    freeMem val
    return (result', val')

data ByteReaderGetInt32BeMethodInfo
instance (signature ~ (m (Bool,Int32)), MonadIO m) => O.MethodInfo ByteReaderGetInt32BeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderGetInt32Be

-- method ByteReader::get_int32_le
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #gint32 to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read a signed 32 bit little endian integer into /@val@/
and update the current position.
-}
byteReaderGetInt32Le ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Int32)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderGetInt32Le reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr Int32)
    result <- gst_byte_reader_get_int32_le reader' val
    let result' = (/= 0) result
    val' <- peek val
    touchManagedPtr reader
    freeMem val
    return (result', val')

data ByteReaderGetInt32LeMethodInfo
instance (signature ~ (m (Bool,Int32)), MonadIO m) => O.MethodInfo ByteReaderGetInt32LeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderGetInt32Le

-- method ByteReader::get_int64_be
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TInt64, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #gint64 to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read a signed 64 bit big endian integer into /@val@/
and update the current position.
-}
byteReaderGetInt64Be ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Int64)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderGetInt64Be reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr Int64)
    result <- gst_byte_reader_get_int64_be reader' val
    let result' = (/= 0) result
    val' <- peek val
    touchManagedPtr reader
    freeMem val
    return (result', val')

data ByteReaderGetInt64BeMethodInfo
instance (signature ~ (m (Bool,Int64)), MonadIO m) => O.MethodInfo ByteReaderGetInt64BeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderGetInt64Be

-- method ByteReader::get_int64_le
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TInt64, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #gint64 to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read a signed 64 bit little endian integer into /@val@/
and update the current position.
-}
byteReaderGetInt64Le ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Int64)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderGetInt64Le reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr Int64)
    result <- gst_byte_reader_get_int64_le reader' val
    let result' = (/= 0) result
    val' <- peek val
    touchManagedPtr reader
    freeMem val
    return (result', val')

data ByteReaderGetInt64LeMethodInfo
instance (signature ~ (m (Bool,Int64)), MonadIO m) => O.MethodInfo ByteReaderGetInt64LeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderGetInt64Le

-- method ByteReader::get_int8
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TInt8, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #gint8 to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read a signed 8 bit integer into /@val@/ and update the current position.
-}
byteReaderGetInt8 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Int8)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderGetInt8 reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr Int8)
    result <- gst_byte_reader_get_int8 reader' val
    let result' = (/= 0) result
    val' <- peek val
    touchManagedPtr reader
    freeMem val
    return (result', val')

data ByteReaderGetInt8MethodInfo
instance (signature ~ (m (Bool,Int8)), MonadIO m) => O.MethodInfo ByteReaderGetInt8MethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderGetInt8

-- method ByteReader::get_pos
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader 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_reader_get_pos" gst_byte_reader_get_pos :: 
    Ptr ByteReader ->                       -- reader : TInterface (Name {namespace = "GstBase", name = "ByteReader"})
    IO Word32

{- |
Returns the current position of a 'GI.GstBase.Structs.ByteReader.ByteReader' instance in bytes.
-}
byteReaderGetPos ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m Word32
    {- ^ __Returns:__ The current position of /@reader@/ in bytes. -}
byteReaderGetPos reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    result <- gst_byte_reader_get_pos reader'
    touchManagedPtr reader
    return result

data ByteReaderGetPosMethodInfo
instance (signature ~ (m Word32), MonadIO m) => O.MethodInfo ByteReaderGetPosMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderGetPos

-- method ByteReader::get_remaining
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader 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_reader_get_remaining" gst_byte_reader_get_remaining :: 
    Ptr ByteReader ->                       -- reader : TInterface (Name {namespace = "GstBase", name = "ByteReader"})
    IO Word32

{- |
Returns the remaining number of bytes of a 'GI.GstBase.Structs.ByteReader.ByteReader' instance.
-}
byteReaderGetRemaining ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m Word32
    {- ^ __Returns:__ The remaining number of bytes of /@reader@/ instance. -}
byteReaderGetRemaining reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    result <- gst_byte_reader_get_remaining reader'
    touchManagedPtr reader
    return result

data ByteReaderGetRemainingMethodInfo
instance (signature ~ (m Word32), MonadIO m) => O.MethodInfo ByteReaderGetRemainingMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderGetRemaining

-- method ByteReader::get_size
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader 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_reader_get_size" gst_byte_reader_get_size :: 
    Ptr ByteReader ->                       -- reader : TInterface (Name {namespace = "GstBase", name = "ByteReader"})
    IO Word32

{- |
Returns the total number of bytes of a 'GI.GstBase.Structs.ByteReader.ByteReader' instance.
-}
byteReaderGetSize ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m Word32
    {- ^ __Returns:__ The total number of bytes of /@reader@/ instance. -}
byteReaderGetSize reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    result <- gst_byte_reader_get_size reader'
    touchManagedPtr reader
    return result

data ByteReaderGetSizeMethodInfo
instance (signature ~ (m Word32), MonadIO m) => O.MethodInfo ByteReaderGetSizeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderGetSize

-- method ByteReader::get_string_utf8
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "str", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "address of a\n    #gchar pointer variable in which to store the result", 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_reader_get_string_utf8" gst_byte_reader_get_string_utf8 :: 
    Ptr ByteReader ->                       -- reader : TInterface (Name {namespace = "GstBase", name = "ByteReader"})
    Ptr (Ptr CString) ->                    -- str : TCArray True (-1) (-1) (TBasicType TUTF8)
    IO CInt

{- |
Returns a constant pointer to the current data position if there is
a NUL-terminated string in the data (this could be just a NUL terminator),
advancing the current position to the byte after the string. This will work
for any NUL-terminated string with a character width of 8 bits, so ASCII,
UTF-8, ISO-8859-N etc.

No input checking for valid UTF-8 is done.

This function will fail if no NUL-terminator was found in in the data.
-}
byteReaderGetStringUtf8 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,[T.Text])
    {- ^ __Returns:__ 'True' if a string could be found, 'False' otherwise. -}
byteReaderGetStringUtf8 reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    str <- allocMem :: IO (Ptr (Ptr CString))
    result <- gst_byte_reader_get_string_utf8 reader' str
    let result' = (/= 0) result
    str' <- peek str
    str'' <- unpackZeroTerminatedUTF8CArray str'
    touchManagedPtr reader
    freeMem str
    return (result', str'')

data ByteReaderGetStringUtf8MethodInfo
instance (signature ~ (m (Bool,[T.Text])), MonadIO m) => O.MethodInfo ByteReaderGetStringUtf8MethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderGetStringUtf8

-- method ByteReader::get_uint16_be
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TUInt16, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #guint16 to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read an unsigned 16 bit big endian integer into /@val@/
and update the current position.
-}
byteReaderGetUint16Be ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Word16)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderGetUint16Be reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr Word16)
    result <- gst_byte_reader_get_uint16_be reader' val
    let result' = (/= 0) result
    val' <- peek val
    touchManagedPtr reader
    freeMem val
    return (result', val')

data ByteReaderGetUint16BeMethodInfo
instance (signature ~ (m (Bool,Word16)), MonadIO m) => O.MethodInfo ByteReaderGetUint16BeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderGetUint16Be

-- method ByteReader::get_uint16_le
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TUInt16, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #guint16 to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read an unsigned 16 bit little endian integer into /@val@/
and update the current position.
-}
byteReaderGetUint16Le ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Word16)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderGetUint16Le reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr Word16)
    result <- gst_byte_reader_get_uint16_le reader' val
    let result' = (/= 0) result
    val' <- peek val
    touchManagedPtr reader
    freeMem val
    return (result', val')

data ByteReaderGetUint16LeMethodInfo
instance (signature ~ (m (Bool,Word16)), MonadIO m) => O.MethodInfo ByteReaderGetUint16LeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderGetUint16Le

-- method ByteReader::get_uint24_be
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TUInt32, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #guint32 to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read an unsigned 24 bit big endian integer into /@val@/
and update the current position.
-}
byteReaderGetUint24Be ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Word32)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderGetUint24Be reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr Word32)
    result <- gst_byte_reader_get_uint24_be reader' val
    let result' = (/= 0) result
    val' <- peek val
    touchManagedPtr reader
    freeMem val
    return (result', val')

data ByteReaderGetUint24BeMethodInfo
instance (signature ~ (m (Bool,Word32)), MonadIO m) => O.MethodInfo ByteReaderGetUint24BeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderGetUint24Be

-- method ByteReader::get_uint24_le
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TUInt32, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #guint32 to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read an unsigned 24 bit little endian integer into /@val@/
and update the current position.
-}
byteReaderGetUint24Le ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Word32)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderGetUint24Le reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr Word32)
    result <- gst_byte_reader_get_uint24_le reader' val
    let result' = (/= 0) result
    val' <- peek val
    touchManagedPtr reader
    freeMem val
    return (result', val')

data ByteReaderGetUint24LeMethodInfo
instance (signature ~ (m (Bool,Word32)), MonadIO m) => O.MethodInfo ByteReaderGetUint24LeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderGetUint24Le

-- method ByteReader::get_uint32_be
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TUInt32, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #guint32 to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read an unsigned 32 bit big endian integer into /@val@/
and update the current position.
-}
byteReaderGetUint32Be ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Word32)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderGetUint32Be reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr Word32)
    result <- gst_byte_reader_get_uint32_be reader' val
    let result' = (/= 0) result
    val' <- peek val
    touchManagedPtr reader
    freeMem val
    return (result', val')

data ByteReaderGetUint32BeMethodInfo
instance (signature ~ (m (Bool,Word32)), MonadIO m) => O.MethodInfo ByteReaderGetUint32BeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderGetUint32Be

-- method ByteReader::get_uint32_le
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TUInt32, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #guint32 to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read an unsigned 32 bit little endian integer into /@val@/
and update the current position.
-}
byteReaderGetUint32Le ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Word32)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderGetUint32Le reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr Word32)
    result <- gst_byte_reader_get_uint32_le reader' val
    let result' = (/= 0) result
    val' <- peek val
    touchManagedPtr reader
    freeMem val
    return (result', val')

data ByteReaderGetUint32LeMethodInfo
instance (signature ~ (m (Bool,Word32)), MonadIO m) => O.MethodInfo ByteReaderGetUint32LeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderGetUint32Le

-- method ByteReader::get_uint64_be
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TUInt64, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #guint64 to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read an unsigned 64 bit big endian integer into /@val@/
and update the current position.
-}
byteReaderGetUint64Be ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Word64)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderGetUint64Be reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr Word64)
    result <- gst_byte_reader_get_uint64_be reader' val
    let result' = (/= 0) result
    val' <- peek val
    touchManagedPtr reader
    freeMem val
    return (result', val')

data ByteReaderGetUint64BeMethodInfo
instance (signature ~ (m (Bool,Word64)), MonadIO m) => O.MethodInfo ByteReaderGetUint64BeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderGetUint64Be

-- method ByteReader::get_uint64_le
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TUInt64, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #guint64 to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read an unsigned 64 bit little endian integer into /@val@/
and update the current position.
-}
byteReaderGetUint64Le ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Word64)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderGetUint64Le reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr Word64)
    result <- gst_byte_reader_get_uint64_le reader' val
    let result' = (/= 0) result
    val' <- peek val
    touchManagedPtr reader
    freeMem val
    return (result', val')

data ByteReaderGetUint64LeMethodInfo
instance (signature ~ (m (Bool,Word64)), MonadIO m) => O.MethodInfo ByteReaderGetUint64LeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderGetUint64Le

-- method ByteReader::get_uint8
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TUInt8, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #guint8 to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read an unsigned 8 bit integer into /@val@/ and update the current position.
-}
byteReaderGetUint8 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Word8)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderGetUint8 reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr Word8)
    result <- gst_byte_reader_get_uint8 reader' val
    let result' = (/= 0) result
    val' <- peek val
    touchManagedPtr reader
    freeMem val
    return (result', val')

data ByteReaderGetUint8MethodInfo
instance (signature ~ (m (Bool,Word8)), MonadIO m) => O.MethodInfo ByteReaderGetUint8MethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderGetUint8

-- method ByteReader::init
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader 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 from which\n    the #GstByteReader should read", 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 : Nothing
-- throws : False
-- Skip return : False

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

{- |
Initializes a 'GI.GstBase.Structs.ByteReader.ByteReader' instance to read from /@data@/. This function
can be called on already initialized instances.
-}
byteReaderInit ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> ByteString
    {- ^ /@data@/: data from which
    the 'GI.GstBase.Structs.ByteReader.ByteReader' should read -}
    -> m ()
byteReaderInit reader data_ = liftIO $ do
    let size = fromIntegral $ B.length data_
    reader' <- unsafeManagedPtrGetPtr reader
    data_' <- packByteString data_
    gst_byte_reader_init reader' data_' size
    touchManagedPtr reader
    freeMem data_'
    return ()

data ByteReaderInitMethodInfo
instance (signature ~ (ByteString -> m ()), MonadIO m) => O.MethodInfo ByteReaderInitMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderInit

-- method ByteReader::masked_scan_uint32
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "mask", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "mask to apply to data before matching against @pattern", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "pattern", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "pattern to match (after mask is applied)", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "offset", argType = TBasicType TUInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "offset from which to start scanning, relative to the current\n    position", 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 scan from offset", 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_reader_masked_scan_uint32" gst_byte_reader_masked_scan_uint32 :: 
    Ptr ByteReader ->                       -- reader : TInterface (Name {namespace = "GstBase", name = "ByteReader"})
    Word32 ->                               -- mask : TBasicType TUInt32
    Word32 ->                               -- pattern : TBasicType TUInt32
    Word32 ->                               -- offset : TBasicType TUInt
    Word32 ->                               -- size : TBasicType TUInt
    IO Word32

{- |
Scan for pattern /@pattern@/ with applied mask /@mask@/ in the byte reader data,
starting from offset /@offset@/ relative to the current position.

The bytes in /@pattern@/ and /@mask@/ are interpreted left-to-right, regardless
of endianness.  All four bytes of the pattern must be present in the
byte reader data for it to match, even if the first or last bytes are masked
out.

It is an error to call this function without making sure that there is
enough data (offset+size bytes) in the byte reader.
-}
byteReaderMaskedScanUint32 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' -}
    -> Word32
    {- ^ /@mask@/: mask to apply to data before matching against /@pattern@/ -}
    -> Word32
    {- ^ /@pattern@/: pattern to match (after mask is applied) -}
    -> Word32
    {- ^ /@offset@/: offset from which to start scanning, relative to the current
    position -}
    -> Word32
    {- ^ /@size@/: number of bytes to scan from offset -}
    -> m Word32
    {- ^ __Returns:__ offset of the first match, or -1 if no match was found.

Example:
\<programlisting>
\/\/ Assume the reader contains 0x00 0x01 0x02 ... 0xfe 0xff

gst_byte_reader_masked_scan_uint32 (reader, 0xffffffff, 0x00010203, 0, 256);
\/\/ -> returns 0
gst_byte_reader_masked_scan_uint32 (reader, 0xffffffff, 0x00010203, 1, 255);
\/\/ -> returns -1
gst_byte_reader_masked_scan_uint32 (reader, 0xffffffff, 0x01020304, 1, 255);
\/\/ -> returns 1
gst_byte_reader_masked_scan_uint32 (reader, 0xffff, 0x0001, 0, 256);
\/\/ -> returns -1
gst_byte_reader_masked_scan_uint32 (reader, 0xffff, 0x0203, 0, 256);
\/\/ -> returns 0
gst_byte_reader_masked_scan_uint32 (reader, 0xffff0000, 0x02030000, 0, 256);
\/\/ -> returns 2
gst_byte_reader_masked_scan_uint32 (reader, 0xffff0000, 0x02030000, 0, 4);
\/\/ -> returns -1
\<\/programlisting> -}
byteReaderMaskedScanUint32 reader mask pattern offset size = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    result <- gst_byte_reader_masked_scan_uint32 reader' mask pattern offset size
    touchManagedPtr reader
    return result

data ByteReaderMaskedScanUint32MethodInfo
instance (signature ~ (Word32 -> Word32 -> Word32 -> Word32 -> m Word32), MonadIO m) => O.MethodInfo ByteReaderMaskedScanUint32MethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderMaskedScanUint32

-- method ByteReader::masked_scan_uint32_peek
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "mask", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "mask to apply to data before matching against @pattern", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "pattern", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "pattern to match (after mask is applied)", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "offset", argType = TBasicType TUInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "offset from which to start scanning, relative to the current\n    position", 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 scan from offset", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "value", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "pointer to uint32 to return matching data", 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_reader_masked_scan_uint32_peek" gst_byte_reader_masked_scan_uint32_peek :: 
    Ptr ByteReader ->                       -- reader : TInterface (Name {namespace = "GstBase", name = "ByteReader"})
    Word32 ->                               -- mask : TBasicType TUInt32
    Word32 ->                               -- pattern : TBasicType TUInt32
    Word32 ->                               -- offset : TBasicType TUInt
    Word32 ->                               -- size : TBasicType TUInt
    Word32 ->                               -- value : TBasicType TUInt32
    IO Word32

{- |
Scan for pattern /@pattern@/ with applied mask /@mask@/ in the byte reader data,
starting from offset /@offset@/ relative to the current position.

The bytes in /@pattern@/ and /@mask@/ are interpreted left-to-right, regardless
of endianness.  All four bytes of the pattern must be present in the
byte reader data for it to match, even if the first or last bytes are masked
out.

It is an error to call this function without making sure that there is
enough data (offset+size bytes) in the byte reader.

@since 1.6
-}
byteReaderMaskedScanUint32Peek ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' -}
    -> Word32
    {- ^ /@mask@/: mask to apply to data before matching against /@pattern@/ -}
    -> Word32
    {- ^ /@pattern@/: pattern to match (after mask is applied) -}
    -> Word32
    {- ^ /@offset@/: offset from which to start scanning, relative to the current
    position -}
    -> Word32
    {- ^ /@size@/: number of bytes to scan from offset -}
    -> Word32
    {- ^ /@value@/: pointer to uint32 to return matching data -}
    -> m Word32
    {- ^ __Returns:__ offset of the first match, or -1 if no match was found. -}
byteReaderMaskedScanUint32Peek reader mask pattern offset size value = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    result <- gst_byte_reader_masked_scan_uint32_peek reader' mask pattern offset size value
    touchManagedPtr reader
    return result

data ByteReaderMaskedScanUint32PeekMethodInfo
instance (signature ~ (Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> m Word32), MonadIO m) => O.MethodInfo ByteReaderMaskedScanUint32PeekMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderMaskedScanUint32Peek

-- method ByteReader::peek_data
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "size", argType = TBasicType TUInt, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Size in bytes", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything},Arg {argCName = "val", argType = TCArray False (-1) 1 (TBasicType TUInt8), direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "address of a\n    #guint8 pointer variable in which to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : [Arg {argCName = "size", argType = TBasicType TUInt, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Size in bytes", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gst_byte_reader_peek_data" gst_byte_reader_peek_data :: 
    Ptr ByteReader ->                       -- reader : TInterface (Name {namespace = "GstBase", name = "ByteReader"})
    Ptr Word32 ->                           -- size : TBasicType TUInt
    Ptr (Ptr Word8) ->                      -- val : TCArray False (-1) 1 (TBasicType TUInt8)
    IO CInt

{- |
Returns a constant pointer to the current data
position if at least /@size@/ bytes are left and
keeps the current position.
-}
byteReaderPeekData ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,ByteString)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderPeekData reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    size <- allocMem :: IO (Ptr Word32)
    val <- allocMem :: IO (Ptr (Ptr Word8))
    result <- gst_byte_reader_peek_data reader' size val
    size' <- peek size
    let result' = (/= 0) result
    val' <- peek val
    val'' <- (unpackByteStringWithLength size') val'
    touchManagedPtr reader
    freeMem size
    freeMem val
    return (result', val'')

data ByteReaderPeekDataMethodInfo
instance (signature ~ (m (Bool,ByteString)), MonadIO m) => O.MethodInfo ByteReaderPeekDataMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderPeekData

-- method ByteReader::peek_float32_be
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TFloat, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #gfloat to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read a 32 bit big endian floating point value into /@val@/
but keep the current position.
-}
byteReaderPeekFloat32Be ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Float)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderPeekFloat32Be reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr CFloat)
    result <- gst_byte_reader_peek_float32_be reader' val
    let result' = (/= 0) result
    val' <- peek val
    let val'' = realToFrac val'
    touchManagedPtr reader
    freeMem val
    return (result', val'')

data ByteReaderPeekFloat32BeMethodInfo
instance (signature ~ (m (Bool,Float)), MonadIO m) => O.MethodInfo ByteReaderPeekFloat32BeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderPeekFloat32Be

-- method ByteReader::peek_float32_le
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TFloat, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #gfloat to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read a 32 bit little endian floating point value into /@val@/
but keep the current position.
-}
byteReaderPeekFloat32Le ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Float)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderPeekFloat32Le reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr CFloat)
    result <- gst_byte_reader_peek_float32_le reader' val
    let result' = (/= 0) result
    val' <- peek val
    let val'' = realToFrac val'
    touchManagedPtr reader
    freeMem val
    return (result', val'')

data ByteReaderPeekFloat32LeMethodInfo
instance (signature ~ (m (Bool,Float)), MonadIO m) => O.MethodInfo ByteReaderPeekFloat32LeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderPeekFloat32Le

-- method ByteReader::peek_float64_be
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TDouble, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #gdouble to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read a 64 bit big endian floating point value into /@val@/
but keep the current position.
-}
byteReaderPeekFloat64Be ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Double)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderPeekFloat64Be reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr CDouble)
    result <- gst_byte_reader_peek_float64_be reader' val
    let result' = (/= 0) result
    val' <- peek val
    let val'' = realToFrac val'
    touchManagedPtr reader
    freeMem val
    return (result', val'')

data ByteReaderPeekFloat64BeMethodInfo
instance (signature ~ (m (Bool,Double)), MonadIO m) => O.MethodInfo ByteReaderPeekFloat64BeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderPeekFloat64Be

-- method ByteReader::peek_float64_le
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TDouble, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #gdouble to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read a 64 bit little endian floating point value into /@val@/
but keep the current position.
-}
byteReaderPeekFloat64Le ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Double)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderPeekFloat64Le reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr CDouble)
    result <- gst_byte_reader_peek_float64_le reader' val
    let result' = (/= 0) result
    val' <- peek val
    let val'' = realToFrac val'
    touchManagedPtr reader
    freeMem val
    return (result', val'')

data ByteReaderPeekFloat64LeMethodInfo
instance (signature ~ (m (Bool,Double)), MonadIO m) => O.MethodInfo ByteReaderPeekFloat64LeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderPeekFloat64Le

-- method ByteReader::peek_int16_be
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TInt16, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #gint16 to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read a signed 16 bit big endian integer into /@val@/
but keep the current position.
-}
byteReaderPeekInt16Be ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Int16)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderPeekInt16Be reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr Int16)
    result <- gst_byte_reader_peek_int16_be reader' val
    let result' = (/= 0) result
    val' <- peek val
    touchManagedPtr reader
    freeMem val
    return (result', val')

data ByteReaderPeekInt16BeMethodInfo
instance (signature ~ (m (Bool,Int16)), MonadIO m) => O.MethodInfo ByteReaderPeekInt16BeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderPeekInt16Be

-- method ByteReader::peek_int16_le
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TInt16, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #gint16 to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read a signed 16 bit little endian integer into /@val@/
but keep the current position.
-}
byteReaderPeekInt16Le ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Int16)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderPeekInt16Le reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr Int16)
    result <- gst_byte_reader_peek_int16_le reader' val
    let result' = (/= 0) result
    val' <- peek val
    touchManagedPtr reader
    freeMem val
    return (result', val')

data ByteReaderPeekInt16LeMethodInfo
instance (signature ~ (m (Bool,Int16)), MonadIO m) => O.MethodInfo ByteReaderPeekInt16LeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderPeekInt16Le

-- method ByteReader::peek_int24_be
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #gint32 to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read a signed 24 bit big endian integer into /@val@/
but keep the current position.
-}
byteReaderPeekInt24Be ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Int32)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderPeekInt24Be reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr Int32)
    result <- gst_byte_reader_peek_int24_be reader' val
    let result' = (/= 0) result
    val' <- peek val
    touchManagedPtr reader
    freeMem val
    return (result', val')

data ByteReaderPeekInt24BeMethodInfo
instance (signature ~ (m (Bool,Int32)), MonadIO m) => O.MethodInfo ByteReaderPeekInt24BeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderPeekInt24Be

-- method ByteReader::peek_int24_le
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #gint32 to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read a signed 24 bit little endian integer into /@val@/
but keep the current position.
-}
byteReaderPeekInt24Le ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Int32)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderPeekInt24Le reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr Int32)
    result <- gst_byte_reader_peek_int24_le reader' val
    let result' = (/= 0) result
    val' <- peek val
    touchManagedPtr reader
    freeMem val
    return (result', val')

data ByteReaderPeekInt24LeMethodInfo
instance (signature ~ (m (Bool,Int32)), MonadIO m) => O.MethodInfo ByteReaderPeekInt24LeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderPeekInt24Le

-- method ByteReader::peek_int32_be
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #gint32 to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read a signed 32 bit big endian integer into /@val@/
but keep the current position.
-}
byteReaderPeekInt32Be ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Int32)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderPeekInt32Be reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr Int32)
    result <- gst_byte_reader_peek_int32_be reader' val
    let result' = (/= 0) result
    val' <- peek val
    touchManagedPtr reader
    freeMem val
    return (result', val')

data ByteReaderPeekInt32BeMethodInfo
instance (signature ~ (m (Bool,Int32)), MonadIO m) => O.MethodInfo ByteReaderPeekInt32BeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderPeekInt32Be

-- method ByteReader::peek_int32_le
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #gint32 to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read a signed 32 bit little endian integer into /@val@/
but keep the current position.
-}
byteReaderPeekInt32Le ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Int32)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderPeekInt32Le reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr Int32)
    result <- gst_byte_reader_peek_int32_le reader' val
    let result' = (/= 0) result
    val' <- peek val
    touchManagedPtr reader
    freeMem val
    return (result', val')

data ByteReaderPeekInt32LeMethodInfo
instance (signature ~ (m (Bool,Int32)), MonadIO m) => O.MethodInfo ByteReaderPeekInt32LeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderPeekInt32Le

-- method ByteReader::peek_int64_be
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TInt64, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #gint64 to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read a signed 64 bit big endian integer into /@val@/
but keep the current position.
-}
byteReaderPeekInt64Be ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Int64)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderPeekInt64Be reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr Int64)
    result <- gst_byte_reader_peek_int64_be reader' val
    let result' = (/= 0) result
    val' <- peek val
    touchManagedPtr reader
    freeMem val
    return (result', val')

data ByteReaderPeekInt64BeMethodInfo
instance (signature ~ (m (Bool,Int64)), MonadIO m) => O.MethodInfo ByteReaderPeekInt64BeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderPeekInt64Be

-- method ByteReader::peek_int64_le
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TInt64, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #gint64 to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read a signed 64 bit little endian integer into /@val@/
but keep the current position.
-}
byteReaderPeekInt64Le ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Int64)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderPeekInt64Le reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr Int64)
    result <- gst_byte_reader_peek_int64_le reader' val
    let result' = (/= 0) result
    val' <- peek val
    touchManagedPtr reader
    freeMem val
    return (result', val')

data ByteReaderPeekInt64LeMethodInfo
instance (signature ~ (m (Bool,Int64)), MonadIO m) => O.MethodInfo ByteReaderPeekInt64LeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderPeekInt64Le

-- method ByteReader::peek_int8
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TInt8, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #gint8 to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read a signed 8 bit integer into /@val@/ but keep the current position.
-}
byteReaderPeekInt8 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Int8)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderPeekInt8 reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr Int8)
    result <- gst_byte_reader_peek_int8 reader' val
    let result' = (/= 0) result
    val' <- peek val
    touchManagedPtr reader
    freeMem val
    return (result', val')

data ByteReaderPeekInt8MethodInfo
instance (signature ~ (m (Bool,Int8)), MonadIO m) => O.MethodInfo ByteReaderPeekInt8MethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderPeekInt8

-- method ByteReader::peek_string_utf8
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "str", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "address of a\n    #gchar pointer variable in which to store the result", 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_reader_peek_string_utf8" gst_byte_reader_peek_string_utf8 :: 
    Ptr ByteReader ->                       -- reader : TInterface (Name {namespace = "GstBase", name = "ByteReader"})
    Ptr (Ptr CString) ->                    -- str : TCArray True (-1) (-1) (TBasicType TUTF8)
    IO CInt

{- |
Returns a constant pointer to the current data position if there is
a NUL-terminated string in the data (this could be just a NUL terminator).
The current position will be maintained. This will work for any
NUL-terminated string with a character width of 8 bits, so ASCII,
UTF-8, ISO-8859-N etc.

No input checking for valid UTF-8 is done.

This function will fail if no NUL-terminator was found in in the data.
-}
byteReaderPeekStringUtf8 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,[T.Text])
    {- ^ __Returns:__ 'True' if a string could be skipped, 'False' otherwise. -}
byteReaderPeekStringUtf8 reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    str <- allocMem :: IO (Ptr (Ptr CString))
    result <- gst_byte_reader_peek_string_utf8 reader' str
    let result' = (/= 0) result
    str' <- peek str
    str'' <- unpackZeroTerminatedUTF8CArray str'
    touchManagedPtr reader
    freeMem str
    return (result', str'')

data ByteReaderPeekStringUtf8MethodInfo
instance (signature ~ (m (Bool,[T.Text])), MonadIO m) => O.MethodInfo ByteReaderPeekStringUtf8MethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderPeekStringUtf8

-- method ByteReader::peek_uint16_be
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TUInt16, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #guint16 to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read an unsigned 16 bit big endian integer into /@val@/
but keep the current position.
-}
byteReaderPeekUint16Be ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Word16)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderPeekUint16Be reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr Word16)
    result <- gst_byte_reader_peek_uint16_be reader' val
    let result' = (/= 0) result
    val' <- peek val
    touchManagedPtr reader
    freeMem val
    return (result', val')

data ByteReaderPeekUint16BeMethodInfo
instance (signature ~ (m (Bool,Word16)), MonadIO m) => O.MethodInfo ByteReaderPeekUint16BeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderPeekUint16Be

-- method ByteReader::peek_uint16_le
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TUInt16, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #guint16 to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read an unsigned 16 bit little endian integer into /@val@/
but keep the current position.
-}
byteReaderPeekUint16Le ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Word16)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderPeekUint16Le reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr Word16)
    result <- gst_byte_reader_peek_uint16_le reader' val
    let result' = (/= 0) result
    val' <- peek val
    touchManagedPtr reader
    freeMem val
    return (result', val')

data ByteReaderPeekUint16LeMethodInfo
instance (signature ~ (m (Bool,Word16)), MonadIO m) => O.MethodInfo ByteReaderPeekUint16LeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderPeekUint16Le

-- method ByteReader::peek_uint24_be
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TUInt32, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #guint32 to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read an unsigned 24 bit big endian integer into /@val@/
but keep the current position.
-}
byteReaderPeekUint24Be ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Word32)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderPeekUint24Be reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr Word32)
    result <- gst_byte_reader_peek_uint24_be reader' val
    let result' = (/= 0) result
    val' <- peek val
    touchManagedPtr reader
    freeMem val
    return (result', val')

data ByteReaderPeekUint24BeMethodInfo
instance (signature ~ (m (Bool,Word32)), MonadIO m) => O.MethodInfo ByteReaderPeekUint24BeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderPeekUint24Be

-- method ByteReader::peek_uint24_le
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TUInt32, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #guint32 to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read an unsigned 24 bit little endian integer into /@val@/
but keep the current position.
-}
byteReaderPeekUint24Le ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Word32)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderPeekUint24Le reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr Word32)
    result <- gst_byte_reader_peek_uint24_le reader' val
    let result' = (/= 0) result
    val' <- peek val
    touchManagedPtr reader
    freeMem val
    return (result', val')

data ByteReaderPeekUint24LeMethodInfo
instance (signature ~ (m (Bool,Word32)), MonadIO m) => O.MethodInfo ByteReaderPeekUint24LeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderPeekUint24Le

-- method ByteReader::peek_uint32_be
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TUInt32, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #guint32 to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read an unsigned 32 bit big endian integer into /@val@/
but keep the current position.
-}
byteReaderPeekUint32Be ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Word32)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderPeekUint32Be reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr Word32)
    result <- gst_byte_reader_peek_uint32_be reader' val
    let result' = (/= 0) result
    val' <- peek val
    touchManagedPtr reader
    freeMem val
    return (result', val')

data ByteReaderPeekUint32BeMethodInfo
instance (signature ~ (m (Bool,Word32)), MonadIO m) => O.MethodInfo ByteReaderPeekUint32BeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderPeekUint32Be

-- method ByteReader::peek_uint32_le
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TUInt32, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #guint32 to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read an unsigned 32 bit little endian integer into /@val@/
but keep the current position.
-}
byteReaderPeekUint32Le ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Word32)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderPeekUint32Le reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr Word32)
    result <- gst_byte_reader_peek_uint32_le reader' val
    let result' = (/= 0) result
    val' <- peek val
    touchManagedPtr reader
    freeMem val
    return (result', val')

data ByteReaderPeekUint32LeMethodInfo
instance (signature ~ (m (Bool,Word32)), MonadIO m) => O.MethodInfo ByteReaderPeekUint32LeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderPeekUint32Le

-- method ByteReader::peek_uint64_be
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TUInt64, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #guint64 to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read an unsigned 64 bit big endian integer into /@val@/
but keep the current position.
-}
byteReaderPeekUint64Be ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Word64)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderPeekUint64Be reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr Word64)
    result <- gst_byte_reader_peek_uint64_be reader' val
    let result' = (/= 0) result
    val' <- peek val
    touchManagedPtr reader
    freeMem val
    return (result', val')

data ByteReaderPeekUint64BeMethodInfo
instance (signature ~ (m (Bool,Word64)), MonadIO m) => O.MethodInfo ByteReaderPeekUint64BeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderPeekUint64Be

-- method ByteReader::peek_uint64_le
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TUInt64, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #guint64 to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read an unsigned 64 bit little endian integer into /@val@/
but keep the current position.
-}
byteReaderPeekUint64Le ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Word64)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderPeekUint64Le reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr Word64)
    result <- gst_byte_reader_peek_uint64_le reader' val
    let result' = (/= 0) result
    val' <- peek val
    touchManagedPtr reader
    freeMem val
    return (result', val')

data ByteReaderPeekUint64LeMethodInfo
instance (signature ~ (m (Bool,Word64)), MonadIO m) => O.MethodInfo ByteReaderPeekUint64LeMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderPeekUint64Le

-- method ByteReader::peek_uint8
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "val", argType = TBasicType TUInt8, direction = DirectionOut, mayBeNull = False, argDoc = Documentation {rawDocText = Just "Pointer to a #guint8 to store the result", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

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

{- |
Read an unsigned 8 bit integer into /@val@/ but keep the current position.
-}
byteReaderPeekUint8 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m (Bool,Word8)
    {- ^ __Returns:__ 'True' if successful, 'False' otherwise. -}
byteReaderPeekUint8 reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    val <- allocMem :: IO (Ptr Word8)
    result <- gst_byte_reader_peek_uint8 reader' val
    let result' = (/= 0) result
    val' <- peek val
    touchManagedPtr reader
    freeMem val
    return (result', val')

data ByteReaderPeekUint8MethodInfo
instance (signature ~ (m (Bool,Word8)), MonadIO m) => O.MethodInfo ByteReaderPeekUint8MethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderPeekUint8

-- method ByteReader::set_pos
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "pos", argType = TBasicType TUInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "The new position in bytes", 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_reader_set_pos" gst_byte_reader_set_pos :: 
    Ptr ByteReader ->                       -- reader : TInterface (Name {namespace = "GstBase", name = "ByteReader"})
    Word32 ->                               -- pos : TBasicType TUInt
    IO CInt

{- |
Sets the new position of a 'GI.GstBase.Structs.ByteReader.ByteReader' instance to /@pos@/ in bytes.
-}
byteReaderSetPos ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> Word32
    {- ^ /@pos@/: The new position in bytes -}
    -> m Bool
    {- ^ __Returns:__ 'True' if the position could be set successfully, 'False'
otherwise. -}
byteReaderSetPos reader pos = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    result <- gst_byte_reader_set_pos reader' pos
    let result' = (/= 0) result
    touchManagedPtr reader
    return result'

data ByteReaderSetPosMethodInfo
instance (signature ~ (Word32 -> m Bool), MonadIO m) => O.MethodInfo ByteReaderSetPosMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderSetPos

-- method ByteReader::skip
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "nbytes", argType = TBasicType TUInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the number of bytes to skip", 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_reader_skip" gst_byte_reader_skip :: 
    Ptr ByteReader ->                       -- reader : TInterface (Name {namespace = "GstBase", name = "ByteReader"})
    Word32 ->                               -- nbytes : TBasicType TUInt
    IO CInt

{- |
Skips /@nbytes@/ bytes of the 'GI.GstBase.Structs.ByteReader.ByteReader' instance.
-}
byteReaderSkip ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> Word32
    {- ^ /@nbytes@/: the number of bytes to skip -}
    -> m Bool
    {- ^ __Returns:__ 'True' if /@nbytes@/ bytes could be skipped, 'False' otherwise. -}
byteReaderSkip reader nbytes = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    result <- gst_byte_reader_skip reader' nbytes
    let result' = (/= 0) result
    touchManagedPtr reader
    return result'

data ByteReaderSkipMethodInfo
instance (signature ~ (Word32 -> m Bool), MonadIO m) => O.MethodInfo ByteReaderSkipMethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderSkip

-- method ByteReader::skip_string_utf16
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", 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_reader_skip_string_utf16" gst_byte_reader_skip_string_utf16 :: 
    Ptr ByteReader ->                       -- reader : TInterface (Name {namespace = "GstBase", name = "ByteReader"})
    IO CInt

{- |
Skips a NUL-terminated UTF-16 string in the 'GI.GstBase.Structs.ByteReader.ByteReader' instance,
advancing the current position to the byte after the string.

No input checking for valid UTF-16 is done.

This function will fail if no NUL-terminator was found in in the data.
-}
byteReaderSkipStringUtf16 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m Bool
    {- ^ __Returns:__ 'True' if a string could be skipped, 'False' otherwise. -}
byteReaderSkipStringUtf16 reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    result <- gst_byte_reader_skip_string_utf16 reader'
    let result' = (/= 0) result
    touchManagedPtr reader
    return result'

data ByteReaderSkipStringUtf16MethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo ByteReaderSkipStringUtf16MethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderSkipStringUtf16

-- method ByteReader::skip_string_utf32
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", 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_reader_skip_string_utf32" gst_byte_reader_skip_string_utf32 :: 
    Ptr ByteReader ->                       -- reader : TInterface (Name {namespace = "GstBase", name = "ByteReader"})
    IO CInt

{- |
Skips a NUL-terminated UTF-32 string in the 'GI.GstBase.Structs.ByteReader.ByteReader' instance,
advancing the current position to the byte after the string.

No input checking for valid UTF-32 is done.

This function will fail if no NUL-terminator was found in in the data.
-}
byteReaderSkipStringUtf32 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m Bool
    {- ^ __Returns:__ 'True' if a string could be skipped, 'False' otherwise. -}
byteReaderSkipStringUtf32 reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    result <- gst_byte_reader_skip_string_utf32 reader'
    let result' = (/= 0) result
    touchManagedPtr reader
    return result'

data ByteReaderSkipStringUtf32MethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo ByteReaderSkipStringUtf32MethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderSkipStringUtf32

-- method ByteReader::skip_string_utf8
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "reader", argType = TInterface (Name {namespace = "GstBase", name = "ByteReader"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstByteReader instance", 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_reader_skip_string_utf8" gst_byte_reader_skip_string_utf8 :: 
    Ptr ByteReader ->                       -- reader : TInterface (Name {namespace = "GstBase", name = "ByteReader"})
    IO CInt

{- |
Skips a NUL-terminated string in the 'GI.GstBase.Structs.ByteReader.ByteReader' instance, advancing
the current position to the byte after the string. This will work for
any NUL-terminated string with a character width of 8 bits, so ASCII,
UTF-8, ISO-8859-N etc. No input checking for valid UTF-8 is done.

This function will fail if no NUL-terminator was found in in the data.
-}
byteReaderSkipStringUtf8 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteReader
    {- ^ /@reader@/: a 'GI.GstBase.Structs.ByteReader.ByteReader' instance -}
    -> m Bool
    {- ^ __Returns:__ 'True' if a string could be skipped, 'False' otherwise. -}
byteReaderSkipStringUtf8 reader = liftIO $ do
    reader' <- unsafeManagedPtrGetPtr reader
    result <- gst_byte_reader_skip_string_utf8 reader'
    let result' = (/= 0) result
    touchManagedPtr reader
    return result'

data ByteReaderSkipStringUtf8MethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo ByteReaderSkipStringUtf8MethodInfo ByteReader signature where
    overloadedMethod _ = byteReaderSkipStringUtf8

type family ResolveByteReaderMethod (t :: Symbol) (o :: *) :: * where
    ResolveByteReaderMethod "dupData" o = ByteReaderDupDataMethodInfo
    ResolveByteReaderMethod "dupStringUtf16" o = ByteReaderDupStringUtf16MethodInfo
    ResolveByteReaderMethod "dupStringUtf32" o = ByteReaderDupStringUtf32MethodInfo
    ResolveByteReaderMethod "dupStringUtf8" o = ByteReaderDupStringUtf8MethodInfo
    ResolveByteReaderMethod "free" o = ByteReaderFreeMethodInfo
    ResolveByteReaderMethod "init" o = ByteReaderInitMethodInfo
    ResolveByteReaderMethod "maskedScanUint32" o = ByteReaderMaskedScanUint32MethodInfo
    ResolveByteReaderMethod "maskedScanUint32Peek" o = ByteReaderMaskedScanUint32PeekMethodInfo
    ResolveByteReaderMethod "peekData" o = ByteReaderPeekDataMethodInfo
    ResolveByteReaderMethod "peekFloat32Be" o = ByteReaderPeekFloat32BeMethodInfo
    ResolveByteReaderMethod "peekFloat32Le" o = ByteReaderPeekFloat32LeMethodInfo
    ResolveByteReaderMethod "peekFloat64Be" o = ByteReaderPeekFloat64BeMethodInfo
    ResolveByteReaderMethod "peekFloat64Le" o = ByteReaderPeekFloat64LeMethodInfo
    ResolveByteReaderMethod "peekInt16Be" o = ByteReaderPeekInt16BeMethodInfo
    ResolveByteReaderMethod "peekInt16Le" o = ByteReaderPeekInt16LeMethodInfo
    ResolveByteReaderMethod "peekInt24Be" o = ByteReaderPeekInt24BeMethodInfo
    ResolveByteReaderMethod "peekInt24Le" o = ByteReaderPeekInt24LeMethodInfo
    ResolveByteReaderMethod "peekInt32Be" o = ByteReaderPeekInt32BeMethodInfo
    ResolveByteReaderMethod "peekInt32Le" o = ByteReaderPeekInt32LeMethodInfo
    ResolveByteReaderMethod "peekInt64Be" o = ByteReaderPeekInt64BeMethodInfo
    ResolveByteReaderMethod "peekInt64Le" o = ByteReaderPeekInt64LeMethodInfo
    ResolveByteReaderMethod "peekInt8" o = ByteReaderPeekInt8MethodInfo
    ResolveByteReaderMethod "peekStringUtf8" o = ByteReaderPeekStringUtf8MethodInfo
    ResolveByteReaderMethod "peekUint16Be" o = ByteReaderPeekUint16BeMethodInfo
    ResolveByteReaderMethod "peekUint16Le" o = ByteReaderPeekUint16LeMethodInfo
    ResolveByteReaderMethod "peekUint24Be" o = ByteReaderPeekUint24BeMethodInfo
    ResolveByteReaderMethod "peekUint24Le" o = ByteReaderPeekUint24LeMethodInfo
    ResolveByteReaderMethod "peekUint32Be" o = ByteReaderPeekUint32BeMethodInfo
    ResolveByteReaderMethod "peekUint32Le" o = ByteReaderPeekUint32LeMethodInfo
    ResolveByteReaderMethod "peekUint64Be" o = ByteReaderPeekUint64BeMethodInfo
    ResolveByteReaderMethod "peekUint64Le" o = ByteReaderPeekUint64LeMethodInfo
    ResolveByteReaderMethod "peekUint8" o = ByteReaderPeekUint8MethodInfo
    ResolveByteReaderMethod "skip" o = ByteReaderSkipMethodInfo
    ResolveByteReaderMethod "skipStringUtf16" o = ByteReaderSkipStringUtf16MethodInfo
    ResolveByteReaderMethod "skipStringUtf32" o = ByteReaderSkipStringUtf32MethodInfo
    ResolveByteReaderMethod "skipStringUtf8" o = ByteReaderSkipStringUtf8MethodInfo
    ResolveByteReaderMethod "getData" o = ByteReaderGetDataMethodInfo
    ResolveByteReaderMethod "getFloat32Be" o = ByteReaderGetFloat32BeMethodInfo
    ResolveByteReaderMethod "getFloat32Le" o = ByteReaderGetFloat32LeMethodInfo
    ResolveByteReaderMethod "getFloat64Be" o = ByteReaderGetFloat64BeMethodInfo
    ResolveByteReaderMethod "getFloat64Le" o = ByteReaderGetFloat64LeMethodInfo
    ResolveByteReaderMethod "getInt16Be" o = ByteReaderGetInt16BeMethodInfo
    ResolveByteReaderMethod "getInt16Le" o = ByteReaderGetInt16LeMethodInfo
    ResolveByteReaderMethod "getInt24Be" o = ByteReaderGetInt24BeMethodInfo
    ResolveByteReaderMethod "getInt24Le" o = ByteReaderGetInt24LeMethodInfo
    ResolveByteReaderMethod "getInt32Be" o = ByteReaderGetInt32BeMethodInfo
    ResolveByteReaderMethod "getInt32Le" o = ByteReaderGetInt32LeMethodInfo
    ResolveByteReaderMethod "getInt64Be" o = ByteReaderGetInt64BeMethodInfo
    ResolveByteReaderMethod "getInt64Le" o = ByteReaderGetInt64LeMethodInfo
    ResolveByteReaderMethod "getInt8" o = ByteReaderGetInt8MethodInfo
    ResolveByteReaderMethod "getPos" o = ByteReaderGetPosMethodInfo
    ResolveByteReaderMethod "getRemaining" o = ByteReaderGetRemainingMethodInfo
    ResolveByteReaderMethod "getSize" o = ByteReaderGetSizeMethodInfo
    ResolveByteReaderMethod "getStringUtf8" o = ByteReaderGetStringUtf8MethodInfo
    ResolveByteReaderMethod "getUint16Be" o = ByteReaderGetUint16BeMethodInfo
    ResolveByteReaderMethod "getUint16Le" o = ByteReaderGetUint16LeMethodInfo
    ResolveByteReaderMethod "getUint24Be" o = ByteReaderGetUint24BeMethodInfo
    ResolveByteReaderMethod "getUint24Le" o = ByteReaderGetUint24LeMethodInfo
    ResolveByteReaderMethod "getUint32Be" o = ByteReaderGetUint32BeMethodInfo
    ResolveByteReaderMethod "getUint32Le" o = ByteReaderGetUint32LeMethodInfo
    ResolveByteReaderMethod "getUint64Be" o = ByteReaderGetUint64BeMethodInfo
    ResolveByteReaderMethod "getUint64Le" o = ByteReaderGetUint64LeMethodInfo
    ResolveByteReaderMethod "getUint8" o = ByteReaderGetUint8MethodInfo
    ResolveByteReaderMethod "setPos" o = ByteReaderSetPosMethodInfo
    ResolveByteReaderMethod l o = O.MethodResolutionFailed l o

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

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