{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (inaki@blueleaf.cc)
-}

#define ENABLE_OVERLOADING (MIN_VERSION_haskell_gi_overloading(1,0,0) \
       && !defined(__HADDOCK_VERSION__))

module GI.GstVideo.Callbacks
    (

 -- * Signals
-- ** VideoAffineTransformationGetMatrix #signal:VideoAffineTransformationGetMatrix#

    C_VideoAffineTransformationGetMatrix    ,
    VideoAffineTransformationGetMatrix      ,
    dynamic_VideoAffineTransformationGetMatrix,
    genClosure_VideoAffineTransformationGetMatrix,
    mk_VideoAffineTransformationGetMatrix   ,
    noVideoAffineTransformationGetMatrix    ,
    wrap_VideoAffineTransformationGetMatrix ,


-- ** VideoConvertSampleCallback #signal:VideoConvertSampleCallback#

    C_VideoConvertSampleCallback            ,
    VideoConvertSampleCallback              ,
    VideoConvertSampleCallback_WithClosures ,
    drop_closures_VideoConvertSampleCallback,
    dynamic_VideoConvertSampleCallback      ,
    genClosure_VideoConvertSampleCallback   ,
    mk_VideoConvertSampleCallback           ,
    noVideoConvertSampleCallback            ,
    noVideoConvertSampleCallback_WithClosures,
    wrap_VideoConvertSampleCallback         ,


-- ** VideoFormatPack #signal:VideoFormatPack#

    C_VideoFormatPack                       ,
    VideoFormatPack                         ,
    dynamic_VideoFormatPack                 ,
    genClosure_VideoFormatPack              ,
    mk_VideoFormatPack                      ,
    noVideoFormatPack                       ,
    wrap_VideoFormatPack                    ,


-- ** VideoFormatUnpack #signal:VideoFormatUnpack#

    C_VideoFormatUnpack                     ,
    VideoFormatUnpack                       ,
    dynamic_VideoFormatUnpack               ,
    genClosure_VideoFormatUnpack            ,
    mk_VideoFormatUnpack                    ,
    noVideoFormatUnpack                     ,
    wrap_VideoFormatUnpack                  ,


-- ** VideoGLTextureUpload #signal:VideoGLTextureUpload#

    C_VideoGLTextureUpload                  ,
    VideoGLTextureUpload                    ,
    dynamic_VideoGLTextureUpload            ,
    genClosure_VideoGLTextureUpload         ,
    mk_VideoGLTextureUpload                 ,
    noVideoGLTextureUpload                  ,
    wrap_VideoGLTextureUpload               ,


-- ** VideoMetaMapFieldCallback #signal:VideoMetaMapFieldCallback#

    C_VideoMetaMapFieldCallback             ,
    VideoMetaMapFieldCallback               ,
    dynamic_VideoMetaMapFieldCallback       ,
    genClosure_VideoMetaMapFieldCallback    ,
    mk_VideoMetaMapFieldCallback            ,
    noVideoMetaMapFieldCallback             ,
    wrap_VideoMetaMapFieldCallback          ,


-- ** VideoMetaUnmapFieldCallback #signal:VideoMetaUnmapFieldCallback#

    C_VideoMetaUnmapFieldCallback           ,
    VideoMetaUnmapFieldCallback             ,
    dynamic_VideoMetaUnmapFieldCallback     ,
    genClosure_VideoMetaUnmapFieldCallback  ,
    mk_VideoMetaUnmapFieldCallback          ,
    noVideoMetaUnmapFieldCallback           ,
    wrap_VideoMetaUnmapFieldCallback        ,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL

import qualified GI.Gst.Flags as Gst.Flags
import qualified GI.Gst.Structs.MapInfo as Gst.MapInfo
import qualified GI.Gst.Structs.Sample as Gst.Sample
import {-# SOURCE #-} qualified GI.GstVideo.Flags as GstVideo.Flags
import {-# SOURCE #-} qualified GI.GstVideo.Structs.VideoAffineTransformationMeta as GstVideo.VideoAffineTransformationMeta
import {-# SOURCE #-} qualified GI.GstVideo.Structs.VideoFormatInfo as GstVideo.VideoFormatInfo
import {-# SOURCE #-} qualified GI.GstVideo.Structs.VideoGLTextureUploadMeta as GstVideo.VideoGLTextureUploadMeta
import {-# SOURCE #-} qualified GI.GstVideo.Structs.VideoMeta as GstVideo.VideoMeta

-- callback VideoMetaUnmapFieldCallback
--          -> Callable {returnType = Just (TBasicType TBoolean), returnMayBeNull = False, returnTransfer = TransferNothing, returnDocumentation = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, args = [Arg {argCName = "meta", argType = TInterface (Name {namespace = "GstVideo", name = "VideoMeta"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "plane", argType = TBasicType TUInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "info", argType = TInterface (Name {namespace = "Gst", name = "MapInfo"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}], skipReturn = False, callableThrows = False, callableDeprecated = Nothing, callableDocumentation = Documentation {rawDocText = Nothing, sinceVersion = Nothing}}
-- | Type for the callback on the (unwrapped) C side.
type C_VideoMetaUnmapFieldCallback =
    Ptr GstVideo.VideoMeta.VideoMeta ->
    Word32 ->
    Ptr Gst.MapInfo.MapInfo ->
    IO CInt

-- Args : [Arg {argCName = "meta", argType = TInterface (Name {namespace = "GstVideo", name = "VideoMeta"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "plane", argType = TBasicType TUInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "info", argType = TInterface (Name {namespace = "Gst", name = "MapInfo"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Nothing, 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 "dynamic" __dynamic_C_VideoMetaUnmapFieldCallback :: FunPtr C_VideoMetaUnmapFieldCallback -> C_VideoMetaUnmapFieldCallback

-- | Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
dynamic_VideoMetaUnmapFieldCallback ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    FunPtr C_VideoMetaUnmapFieldCallback
    -> GstVideo.VideoMeta.VideoMeta
    -> Word32
    -> Gst.MapInfo.MapInfo
    -> m Bool
dynamic_VideoMetaUnmapFieldCallback __funPtr meta plane info = liftIO $ do
    meta' <- unsafeManagedPtrGetPtr meta
    info' <- unsafeManagedPtrGetPtr info
    result <- (__dynamic_C_VideoMetaUnmapFieldCallback __funPtr) meta' plane info'
    let result' = (/= 0) result
    touchManagedPtr meta
    touchManagedPtr info
    return result'

-- | Generate a function pointer callable from C code, from a `C_VideoMetaUnmapFieldCallback`.
foreign import ccall "wrapper"
    mk_VideoMetaUnmapFieldCallback :: C_VideoMetaUnmapFieldCallback -> IO (FunPtr C_VideoMetaUnmapFieldCallback)

{- |
/No description available in the introspection data./
-}
type VideoMetaUnmapFieldCallback =
    GstVideo.VideoMeta.VideoMeta
    -> Word32
    -> Gst.MapInfo.MapInfo
    -> IO Bool

-- | A convenience synonym for @`Nothing` :: `Maybe` `VideoMetaUnmapFieldCallback`@.
noVideoMetaUnmapFieldCallback :: Maybe VideoMetaUnmapFieldCallback
noVideoMetaUnmapFieldCallback = Nothing

-- | Wrap the callback into a `GClosure`.
genClosure_VideoMetaUnmapFieldCallback :: MonadIO m => VideoMetaUnmapFieldCallback -> m (GClosure C_VideoMetaUnmapFieldCallback)
genClosure_VideoMetaUnmapFieldCallback cb = liftIO $ do
    let cb' = wrap_VideoMetaUnmapFieldCallback Nothing cb
    mk_VideoMetaUnmapFieldCallback cb' >>= B.GClosure.newGClosure


-- | Wrap a `VideoMetaUnmapFieldCallback` into a `C_VideoMetaUnmapFieldCallback`.
wrap_VideoMetaUnmapFieldCallback ::
    Maybe (Ptr (FunPtr C_VideoMetaUnmapFieldCallback)) ->
    VideoMetaUnmapFieldCallback ->
    C_VideoMetaUnmapFieldCallback
wrap_VideoMetaUnmapFieldCallback funptrptr _cb meta plane info = do
    meta' <- (newPtr GstVideo.VideoMeta.VideoMeta) meta
    info' <- (newPtr Gst.MapInfo.MapInfo) info
    result <- _cb  meta' plane info'
    maybeReleaseFunPtr funptrptr
    let result' = (fromIntegral . fromEnum) result
    return result'


-- callback VideoMetaMapFieldCallback
--          -> Callable {returnType = Just (TBasicType TBoolean), returnMayBeNull = False, returnTransfer = TransferNothing, returnDocumentation = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, args = [Arg {argCName = "meta", argType = TInterface (Name {namespace = "GstVideo", name = "VideoMeta"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "plane", argType = TBasicType TUInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "info", argType = TInterface (Name {namespace = "Gst", name = "MapInfo"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "data", argType = TBasicType TPtr, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "stride", argType = TBasicType TInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "flags", argType = TInterface (Name {namespace = "Gst", name = "MapFlags"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}], skipReturn = False, callableThrows = False, callableDeprecated = Nothing, callableDocumentation = Documentation {rawDocText = Nothing, sinceVersion = Nothing}}
-- | Type for the callback on the (unwrapped) C side.
type C_VideoMetaMapFieldCallback =
    Ptr GstVideo.VideoMeta.VideoMeta ->
    Word32 ->
    Ptr Gst.MapInfo.MapInfo ->
    Ptr () ->
    Int32 ->
    CUInt ->
    IO CInt

-- Args : [Arg {argCName = "meta", argType = TInterface (Name {namespace = "GstVideo", name = "VideoMeta"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "plane", argType = TBasicType TUInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "info", argType = TInterface (Name {namespace = "Gst", name = "MapInfo"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "data", argType = TBasicType TPtr, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "stride", argType = TBasicType TInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "flags", argType = TInterface (Name {namespace = "Gst", name = "MapFlags"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Nothing, 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 "dynamic" __dynamic_C_VideoMetaMapFieldCallback :: FunPtr C_VideoMetaMapFieldCallback -> C_VideoMetaMapFieldCallback

-- | Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
dynamic_VideoMetaMapFieldCallback ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    FunPtr C_VideoMetaMapFieldCallback
    -> GstVideo.VideoMeta.VideoMeta
    -> Word32
    -> Gst.MapInfo.MapInfo
    -> Ptr ()
    -> Int32
    -> [Gst.Flags.MapFlags]
    -> m Bool
dynamic_VideoMetaMapFieldCallback __funPtr meta plane info data_ stride flags = liftIO $ do
    meta' <- unsafeManagedPtrGetPtr meta
    info' <- unsafeManagedPtrGetPtr info
    let flags' = gflagsToWord flags
    result <- (__dynamic_C_VideoMetaMapFieldCallback __funPtr) meta' plane info' data_ stride flags'
    let result' = (/= 0) result
    touchManagedPtr meta
    touchManagedPtr info
    return result'

-- | Generate a function pointer callable from C code, from a `C_VideoMetaMapFieldCallback`.
foreign import ccall "wrapper"
    mk_VideoMetaMapFieldCallback :: C_VideoMetaMapFieldCallback -> IO (FunPtr C_VideoMetaMapFieldCallback)

{- |
/No description available in the introspection data./
-}
type VideoMetaMapFieldCallback =
    GstVideo.VideoMeta.VideoMeta
    -> Word32
    -> Gst.MapInfo.MapInfo
    -> Ptr ()
    -> Int32
    -> [Gst.Flags.MapFlags]
    -> IO Bool

-- | A convenience synonym for @`Nothing` :: `Maybe` `VideoMetaMapFieldCallback`@.
noVideoMetaMapFieldCallback :: Maybe VideoMetaMapFieldCallback
noVideoMetaMapFieldCallback = Nothing

-- | Wrap the callback into a `GClosure`.
genClosure_VideoMetaMapFieldCallback :: MonadIO m => VideoMetaMapFieldCallback -> m (GClosure C_VideoMetaMapFieldCallback)
genClosure_VideoMetaMapFieldCallback cb = liftIO $ do
    let cb' = wrap_VideoMetaMapFieldCallback Nothing cb
    mk_VideoMetaMapFieldCallback cb' >>= B.GClosure.newGClosure


-- | Wrap a `VideoMetaMapFieldCallback` into a `C_VideoMetaMapFieldCallback`.
wrap_VideoMetaMapFieldCallback ::
    Maybe (Ptr (FunPtr C_VideoMetaMapFieldCallback)) ->
    VideoMetaMapFieldCallback ->
    C_VideoMetaMapFieldCallback
wrap_VideoMetaMapFieldCallback funptrptr _cb meta plane info data_ stride flags = do
    meta' <- (newPtr GstVideo.VideoMeta.VideoMeta) meta
    info' <- (newPtr Gst.MapInfo.MapInfo) info
    let flags' = wordToGFlags flags
    result <- _cb  meta' plane info' data_ stride flags'
    maybeReleaseFunPtr funptrptr
    let result' = (fromIntegral . fromEnum) result
    return result'


-- callback VideoGLTextureUpload
--          -> Callable {returnType = Just (TBasicType TBoolean), returnMayBeNull = False, returnTransfer = TransferNothing, returnDocumentation = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, args = [Arg {argCName = "meta", argType = TInterface (Name {namespace = "GstVideo", name = "VideoGLTextureUploadMeta"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "texture_id", argType = TBasicType TUInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}], skipReturn = False, callableThrows = False, callableDeprecated = Nothing, callableDocumentation = Documentation {rawDocText = Nothing, sinceVersion = Nothing}}
-- | Type for the callback on the (unwrapped) C side.
type C_VideoGLTextureUpload =
    Ptr GstVideo.VideoGLTextureUploadMeta.VideoGLTextureUploadMeta ->
    Word32 ->
    IO CInt

-- Args : [Arg {argCName = "meta", argType = TInterface (Name {namespace = "GstVideo", name = "VideoGLTextureUploadMeta"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "texture_id", argType = TBasicType TUInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Nothing, 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 "dynamic" __dynamic_C_VideoGLTextureUpload :: FunPtr C_VideoGLTextureUpload -> C_VideoGLTextureUpload

-- | Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
dynamic_VideoGLTextureUpload ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    FunPtr C_VideoGLTextureUpload
    -> GstVideo.VideoGLTextureUploadMeta.VideoGLTextureUploadMeta
    -> Word32
    -> m Bool
dynamic_VideoGLTextureUpload __funPtr meta textureId = liftIO $ do
    meta' <- unsafeManagedPtrGetPtr meta
    result <- (__dynamic_C_VideoGLTextureUpload __funPtr) meta' textureId
    let result' = (/= 0) result
    touchManagedPtr meta
    return result'

-- | Generate a function pointer callable from C code, from a `C_VideoGLTextureUpload`.
foreign import ccall "wrapper"
    mk_VideoGLTextureUpload :: C_VideoGLTextureUpload -> IO (FunPtr C_VideoGLTextureUpload)

{- |
/No description available in the introspection data./
-}
type VideoGLTextureUpload =
    GstVideo.VideoGLTextureUploadMeta.VideoGLTextureUploadMeta
    -> Word32
    -> IO Bool

-- | A convenience synonym for @`Nothing` :: `Maybe` `VideoGLTextureUpload`@.
noVideoGLTextureUpload :: Maybe VideoGLTextureUpload
noVideoGLTextureUpload = Nothing

-- | Wrap the callback into a `GClosure`.
genClosure_VideoGLTextureUpload :: MonadIO m => VideoGLTextureUpload -> m (GClosure C_VideoGLTextureUpload)
genClosure_VideoGLTextureUpload cb = liftIO $ do
    let cb' = wrap_VideoGLTextureUpload Nothing cb
    mk_VideoGLTextureUpload cb' >>= B.GClosure.newGClosure


-- | Wrap a `VideoGLTextureUpload` into a `C_VideoGLTextureUpload`.
wrap_VideoGLTextureUpload ::
    Maybe (Ptr (FunPtr C_VideoGLTextureUpload)) ->
    VideoGLTextureUpload ->
    C_VideoGLTextureUpload
wrap_VideoGLTextureUpload funptrptr _cb meta textureId = do
    meta' <- (newPtr GstVideo.VideoGLTextureUploadMeta.VideoGLTextureUploadMeta) meta
    result <- _cb  meta' textureId
    maybeReleaseFunPtr funptrptr
    let result' = (fromIntegral . fromEnum) result
    return result'


-- callback VideoFormatUnpack
--          -> Callable {returnType = Nothing, returnMayBeNull = False, returnTransfer = TransferNothing, returnDocumentation = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, args = [Arg {argCName = "info", argType = TInterface (Name {namespace = "GstVideo", name = "VideoFormatInfo"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstVideoFormatInfo", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "flags", argType = TInterface (Name {namespace = "GstVideo", name = "VideoPackFlags"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "flags to control the unpacking", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "dest", argType = TBasicType TPtr, direction = DirectionIn, mayBeNull = True, argDoc = Documentation {rawDocText = Just "a destination array", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "data", argType = TBasicType TPtr, direction = DirectionIn, mayBeNull = True, argDoc = Documentation {rawDocText = Just "pointers to the data planes", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "stride", argType = TBasicType TInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "strides of the planes", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "x", argType = TBasicType TInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the x position in the image to start from", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "y", argType = TBasicType TInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the y position in the image to start from", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "width", argType = TBasicType TInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the amount of pixels to unpack.", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}], skipReturn = False, callableThrows = False, callableDeprecated = Nothing, callableDocumentation = Documentation {rawDocText = Just "Unpacks @width pixels from the given planes and strides containing data of\nformat @info. The pixels will be unpacked into @dest with each component\ninterleaved as per @info's unpack_format, which will usually be one of\n#GST_VIDEO_FORMAT_ARGB, #GST_VIDEO_FORMAT_AYUV, #GST_VIDEO_FORMAT_ARGB64 or\n#GST_VIDEO_FORMAT_AYUV64 depending on the format to unpack.\n@dest should at least be big enough to hold @width * bytes_per_pixel bytes\nwhere bytes_per_pixel relates to the unpack format and will usually be\neither 4 or 8 depending on the unpack format. bytes_per_pixel will be\nthe same as the pixel stride for plane 0 for the above formats.\n\nFor subsampled formats, the components will be duplicated in the destination\narray. Reconstruction of the missing components can be performed in a\nseparate step after unpacking.", sinceVersion = Nothing}}
-- | Type for the callback on the (unwrapped) C side.
type C_VideoFormatUnpack =
    Ptr GstVideo.VideoFormatInfo.VideoFormatInfo ->
    CUInt ->
    Ptr () ->
    Ptr () ->
    Int32 ->
    Int32 ->
    Int32 ->
    Int32 ->
    IO ()

-- Args : [Arg {argCName = "info", argType = TInterface (Name {namespace = "GstVideo", name = "VideoFormatInfo"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstVideoFormatInfo", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "flags", argType = TInterface (Name {namespace = "GstVideo", name = "VideoPackFlags"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "flags to control the unpacking", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "dest", argType = TBasicType TPtr, direction = DirectionIn, mayBeNull = True, argDoc = Documentation {rawDocText = Just "a destination array", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "data", argType = TBasicType TPtr, direction = DirectionIn, mayBeNull = True, argDoc = Documentation {rawDocText = Just "pointers to the data planes", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "stride", argType = TBasicType TInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "strides of the planes", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "x", argType = TBasicType TInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the x position in the image to start from", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "y", argType = TBasicType TInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the y position in the image to start from", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "width", argType = TBasicType TInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the amount of pixels to unpack.", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Nothing
-- throws : False
-- Skip return : False

foreign import ccall "dynamic" __dynamic_C_VideoFormatUnpack :: FunPtr C_VideoFormatUnpack -> C_VideoFormatUnpack

-- | Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
dynamic_VideoFormatUnpack ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    FunPtr C_VideoFormatUnpack
    -> GstVideo.VideoFormatInfo.VideoFormatInfo
    {- ^ /@info@/: a 'GI.GstVideo.Structs.VideoFormatInfo.VideoFormatInfo' -}
    -> [GstVideo.Flags.VideoPackFlags]
    {- ^ /@flags@/: flags to control the unpacking -}
    -> Ptr ()
    {- ^ /@dest@/: a destination array -}
    -> Ptr ()
    {- ^ /@data@/: pointers to the data planes -}
    -> Int32
    {- ^ /@stride@/: strides of the planes -}
    -> Int32
    {- ^ /@x@/: the x position in the image to start from -}
    -> Int32
    {- ^ /@y@/: the y position in the image to start from -}
    -> Int32
    {- ^ /@width@/: the amount of pixels to unpack. -}
    -> m ()
dynamic_VideoFormatUnpack __funPtr info flags dest data_ stride x y width = liftIO $ do
    info' <- unsafeManagedPtrGetPtr info
    let flags' = gflagsToWord flags
    (__dynamic_C_VideoFormatUnpack __funPtr) info' flags' dest data_ stride x y width
    touchManagedPtr info
    return ()

-- | Generate a function pointer callable from C code, from a `C_VideoFormatUnpack`.
foreign import ccall "wrapper"
    mk_VideoFormatUnpack :: C_VideoFormatUnpack -> IO (FunPtr C_VideoFormatUnpack)

{- |
Unpacks /@width@/ pixels from the given planes and strides containing data of
format /@info@/. The pixels will be unpacked into /@dest@/ with each component
interleaved as per /@info@/\'s unpack_format, which will usually be one of
@/GST_VIDEO_FORMAT_ARGB/@, @/GST_VIDEO_FORMAT_AYUV/@, @/GST_VIDEO_FORMAT_ARGB64/@ or
@/GST_VIDEO_FORMAT_AYUV64/@ depending on the format to unpack.
/@dest@/ should at least be big enough to hold /@width@/ * bytes_per_pixel bytes
where bytes_per_pixel relates to the unpack format and will usually be
either 4 or 8 depending on the unpack format. bytes_per_pixel will be
the same as the pixel stride for plane 0 for the above formats.

For subsampled formats, the components will be duplicated in the destination
array. Reconstruction of the missing components can be performed in a
separate step after unpacking.
-}
type VideoFormatUnpack =
    GstVideo.VideoFormatInfo.VideoFormatInfo
    {- ^ /@info@/: a 'GI.GstVideo.Structs.VideoFormatInfo.VideoFormatInfo' -}
    -> [GstVideo.Flags.VideoPackFlags]
    {- ^ /@flags@/: flags to control the unpacking -}
    -> Ptr ()
    {- ^ /@dest@/: a destination array -}
    -> Ptr ()
    {- ^ /@data@/: pointers to the data planes -}
    -> Int32
    {- ^ /@stride@/: strides of the planes -}
    -> Int32
    {- ^ /@x@/: the x position in the image to start from -}
    -> Int32
    {- ^ /@y@/: the y position in the image to start from -}
    -> Int32
    {- ^ /@width@/: the amount of pixels to unpack. -}
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `VideoFormatUnpack`@.
noVideoFormatUnpack :: Maybe VideoFormatUnpack
noVideoFormatUnpack = Nothing

-- | Wrap the callback into a `GClosure`.
genClosure_VideoFormatUnpack :: MonadIO m => VideoFormatUnpack -> m (GClosure C_VideoFormatUnpack)
genClosure_VideoFormatUnpack cb = liftIO $ do
    let cb' = wrap_VideoFormatUnpack Nothing cb
    mk_VideoFormatUnpack cb' >>= B.GClosure.newGClosure


-- | Wrap a `VideoFormatUnpack` into a `C_VideoFormatUnpack`.
wrap_VideoFormatUnpack ::
    Maybe (Ptr (FunPtr C_VideoFormatUnpack)) ->
    VideoFormatUnpack ->
    C_VideoFormatUnpack
wrap_VideoFormatUnpack funptrptr _cb info flags dest data_ stride x y width = do
    info' <- (newPtr GstVideo.VideoFormatInfo.VideoFormatInfo) info
    let flags' = wordToGFlags flags
    _cb  info' flags' dest data_ stride x y width
    maybeReleaseFunPtr funptrptr


-- callback VideoFormatPack
--          -> Callable {returnType = Nothing, returnMayBeNull = False, returnTransfer = TransferNothing, returnDocumentation = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, args = [Arg {argCName = "info", argType = TInterface (Name {namespace = "GstVideo", name = "VideoFormatInfo"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstVideoFormatInfo", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "flags", argType = TInterface (Name {namespace = "GstVideo", name = "VideoPackFlags"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "flags to control the packing", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "src", argType = TBasicType TPtr, direction = DirectionIn, mayBeNull = True, argDoc = Documentation {rawDocText = Just "a source array", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "sstride", argType = TBasicType TInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the source array stride", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "data", argType = TBasicType TPtr, direction = DirectionIn, mayBeNull = True, argDoc = Documentation {rawDocText = Just "pointers to the destination data planes", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "stride", argType = TBasicType TInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "strides of the destination planes", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "chroma_site", argType = TInterface (Name {namespace = "GstVideo", name = "VideoChromaSite"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the chroma siting of the target when subsampled (not used)", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "y", argType = TBasicType TInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the y position in the image to pack to", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "width", argType = TBasicType TInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the amount of pixels to pack.", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}], skipReturn = False, callableThrows = False, callableDeprecated = Nothing, callableDocumentation = Documentation {rawDocText = Just "Packs @width pixels from @src to the given planes and strides in the\nformat @info. The pixels from source have each component interleaved\nand will be packed into the planes in @data.\n\nThis function operates on pack_lines lines, meaning that @src should\ncontain at least pack_lines lines with a stride of @sstride and @y\nshould be a multiple of pack_lines.\n\nSubsampled formats will use the horizontally and vertically cosited\ncomponent from the source. Subsampling should be performed before\npacking.\n\nBecause this function does not have a x coordinate, it is not possible to\npack pixels starting from an unaligned position. For tiled images this\nmeans that packing should start from a tile coordinate. For subsampled\nformats this means that a complete pixel needs to be packed.", sinceVersion = Nothing}}
-- | Type for the callback on the (unwrapped) C side.
type C_VideoFormatPack =
    Ptr GstVideo.VideoFormatInfo.VideoFormatInfo ->
    CUInt ->
    Ptr () ->
    Int32 ->
    Ptr () ->
    Int32 ->
    CUInt ->
    Int32 ->
    Int32 ->
    IO ()

-- Args : [Arg {argCName = "info", argType = TInterface (Name {namespace = "GstVideo", name = "VideoFormatInfo"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GstVideoFormatInfo", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "flags", argType = TInterface (Name {namespace = "GstVideo", name = "VideoPackFlags"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "flags to control the packing", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "src", argType = TBasicType TPtr, direction = DirectionIn, mayBeNull = True, argDoc = Documentation {rawDocText = Just "a source array", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "sstride", argType = TBasicType TInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the source array stride", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "data", argType = TBasicType TPtr, direction = DirectionIn, mayBeNull = True, argDoc = Documentation {rawDocText = Just "pointers to the destination data planes", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "stride", argType = TBasicType TInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "strides of the destination planes", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "chroma_site", argType = TInterface (Name {namespace = "GstVideo", name = "VideoChromaSite"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the chroma siting of the target when subsampled (not used)", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "y", argType = TBasicType TInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the y position in the image to pack to", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "width", argType = TBasicType TInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the amount of pixels to pack.", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Nothing
-- throws : False
-- Skip return : False

foreign import ccall "dynamic" __dynamic_C_VideoFormatPack :: FunPtr C_VideoFormatPack -> C_VideoFormatPack

-- | Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
dynamic_VideoFormatPack ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    FunPtr C_VideoFormatPack
    -> GstVideo.VideoFormatInfo.VideoFormatInfo
    {- ^ /@info@/: a 'GI.GstVideo.Structs.VideoFormatInfo.VideoFormatInfo' -}
    -> [GstVideo.Flags.VideoPackFlags]
    {- ^ /@flags@/: flags to control the packing -}
    -> Ptr ()
    {- ^ /@src@/: a source array -}
    -> Int32
    {- ^ /@sstride@/: the source array stride -}
    -> Ptr ()
    {- ^ /@data@/: pointers to the destination data planes -}
    -> Int32
    {- ^ /@stride@/: strides of the destination planes -}
    -> [GstVideo.Flags.VideoChromaSite]
    {- ^ /@chromaSite@/: the chroma siting of the target when subsampled (not used) -}
    -> Int32
    {- ^ /@y@/: the y position in the image to pack to -}
    -> Int32
    {- ^ /@width@/: the amount of pixels to pack. -}
    -> m ()
dynamic_VideoFormatPack __funPtr info flags src sstride data_ stride chromaSite y width = liftIO $ do
    info' <- unsafeManagedPtrGetPtr info
    let flags' = gflagsToWord flags
    let chromaSite' = gflagsToWord chromaSite
    (__dynamic_C_VideoFormatPack __funPtr) info' flags' src sstride data_ stride chromaSite' y width
    touchManagedPtr info
    return ()

-- | Generate a function pointer callable from C code, from a `C_VideoFormatPack`.
foreign import ccall "wrapper"
    mk_VideoFormatPack :: C_VideoFormatPack -> IO (FunPtr C_VideoFormatPack)

{- |
Packs /@width@/ pixels from /@src@/ to the given planes and strides in the
format /@info@/. The pixels from source have each component interleaved
and will be packed into the planes in /@data@/.

This function operates on pack_lines lines, meaning that /@src@/ should
contain at least pack_lines lines with a stride of /@sstride@/ and /@y@/
should be a multiple of pack_lines.

Subsampled formats will use the horizontally and vertically cosited
component from the source. Subsampling should be performed before
packing.

Because this function does not have a x coordinate, it is not possible to
pack pixels starting from an unaligned position. For tiled images this
means that packing should start from a tile coordinate. For subsampled
formats this means that a complete pixel needs to be packed.
-}
type VideoFormatPack =
    GstVideo.VideoFormatInfo.VideoFormatInfo
    {- ^ /@info@/: a 'GI.GstVideo.Structs.VideoFormatInfo.VideoFormatInfo' -}
    -> [GstVideo.Flags.VideoPackFlags]
    {- ^ /@flags@/: flags to control the packing -}
    -> Ptr ()
    {- ^ /@src@/: a source array -}
    -> Int32
    {- ^ /@sstride@/: the source array stride -}
    -> Ptr ()
    {- ^ /@data@/: pointers to the destination data planes -}
    -> Int32
    {- ^ /@stride@/: strides of the destination planes -}
    -> [GstVideo.Flags.VideoChromaSite]
    {- ^ /@chromaSite@/: the chroma siting of the target when subsampled (not used) -}
    -> Int32
    {- ^ /@y@/: the y position in the image to pack to -}
    -> Int32
    {- ^ /@width@/: the amount of pixels to pack. -}
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `VideoFormatPack`@.
noVideoFormatPack :: Maybe VideoFormatPack
noVideoFormatPack = Nothing

-- | Wrap the callback into a `GClosure`.
genClosure_VideoFormatPack :: MonadIO m => VideoFormatPack -> m (GClosure C_VideoFormatPack)
genClosure_VideoFormatPack cb = liftIO $ do
    let cb' = wrap_VideoFormatPack Nothing cb
    mk_VideoFormatPack cb' >>= B.GClosure.newGClosure


-- | Wrap a `VideoFormatPack` into a `C_VideoFormatPack`.
wrap_VideoFormatPack ::
    Maybe (Ptr (FunPtr C_VideoFormatPack)) ->
    VideoFormatPack ->
    C_VideoFormatPack
wrap_VideoFormatPack funptrptr _cb info flags src sstride data_ stride chromaSite y width = do
    info' <- (newPtr GstVideo.VideoFormatInfo.VideoFormatInfo) info
    let flags' = wordToGFlags flags
    let chromaSite' = wordToGFlags chromaSite
    _cb  info' flags' src sstride data_ stride chromaSite' y width
    maybeReleaseFunPtr funptrptr


-- callback VideoConvertSampleCallback
--          -> Callable {returnType = Nothing, returnMayBeNull = False, returnTransfer = TransferNothing, returnDocumentation = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, args = [Arg {argCName = "sample", argType = TInterface (Name {namespace = "Gst", name = "Sample"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "error", argType = TError, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "user_data", argType = TBasicType TPtr, direction = DirectionIn, mayBeNull = True, argDoc = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = 2, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}], skipReturn = False, callableThrows = False, callableDeprecated = Nothing, callableDocumentation = Documentation {rawDocText = Nothing, sinceVersion = Nothing}}
-- | Type for the callback on the (unwrapped) C side.
type C_VideoConvertSampleCallback =
    Ptr Gst.Sample.Sample ->
    Ptr GError ->
    Ptr () ->
    IO ()

-- Args : [Arg {argCName = "sample", argType = TInterface (Name {namespace = "Gst", name = "Sample"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "error", argType = TError, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "user_data", argType = TBasicType TPtr, direction = DirectionIn, mayBeNull = True, argDoc = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = 2, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Nothing
-- throws : False
-- Skip return : False

foreign import ccall "dynamic" __dynamic_C_VideoConvertSampleCallback :: FunPtr C_VideoConvertSampleCallback -> C_VideoConvertSampleCallback

-- | Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
dynamic_VideoConvertSampleCallback ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    FunPtr C_VideoConvertSampleCallback
    -> Gst.Sample.Sample
    -> GError
    -> Ptr ()
    -> m ()
dynamic_VideoConvertSampleCallback __funPtr sample error_ userData = liftIO $ do
    sample' <- unsafeManagedPtrGetPtr sample
    error_' <- unsafeManagedPtrGetPtr error_
    (__dynamic_C_VideoConvertSampleCallback __funPtr) sample' error_' userData
    touchManagedPtr sample
    touchManagedPtr error_
    return ()

-- | Generate a function pointer callable from C code, from a `C_VideoConvertSampleCallback`.
foreign import ccall "wrapper"
    mk_VideoConvertSampleCallback :: C_VideoConvertSampleCallback -> IO (FunPtr C_VideoConvertSampleCallback)

{- |
/No description available in the introspection data./
-}
type VideoConvertSampleCallback =
    Gst.Sample.Sample
    -> GError
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `VideoConvertSampleCallback`@.
noVideoConvertSampleCallback :: Maybe VideoConvertSampleCallback
noVideoConvertSampleCallback = Nothing

{- |
/No description available in the introspection data./
-}
type VideoConvertSampleCallback_WithClosures =
    Gst.Sample.Sample
    -> GError
    -> Ptr ()
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `VideoConvertSampleCallback_WithClosures`@.
noVideoConvertSampleCallback_WithClosures :: Maybe VideoConvertSampleCallback_WithClosures
noVideoConvertSampleCallback_WithClosures = Nothing

-- | A simple wrapper that ignores the closure arguments.
drop_closures_VideoConvertSampleCallback :: VideoConvertSampleCallback -> VideoConvertSampleCallback_WithClosures
drop_closures_VideoConvertSampleCallback _f sample error_ _ = _f sample error_

-- | Wrap the callback into a `GClosure`.
genClosure_VideoConvertSampleCallback :: MonadIO m => VideoConvertSampleCallback -> m (GClosure C_VideoConvertSampleCallback)
genClosure_VideoConvertSampleCallback cb = liftIO $ do
    let cb' = drop_closures_VideoConvertSampleCallback cb
    let cb'' = wrap_VideoConvertSampleCallback Nothing cb'
    mk_VideoConvertSampleCallback cb'' >>= B.GClosure.newGClosure


-- | Wrap a `VideoConvertSampleCallback` into a `C_VideoConvertSampleCallback`.
wrap_VideoConvertSampleCallback ::
    Maybe (Ptr (FunPtr C_VideoConvertSampleCallback)) ->
    VideoConvertSampleCallback_WithClosures ->
    C_VideoConvertSampleCallback
wrap_VideoConvertSampleCallback funptrptr _cb sample error_ userData = do
    B.ManagedPtr.withTransient Gst.Sample.Sample sample $ \sample' -> do
        error_' <- (newBoxed GError) error_
        _cb  sample' error_' userData
        maybeReleaseFunPtr funptrptr


-- callback VideoAffineTransformationGetMatrix
--          -> Callable {returnType = Just (TBasicType TBoolean), returnMayBeNull = False, returnTransfer = TransferNothing, returnDocumentation = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, args = [Arg {argCName = "meta", argType = TInterface (Name {namespace = "GstVideo", name = "VideoAffineTransformationMeta"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "matrix", argType = TBasicType TFloat, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}], skipReturn = False, callableThrows = False, callableDeprecated = Nothing, callableDocumentation = Documentation {rawDocText = Nothing, sinceVersion = Nothing}}
-- | Type for the callback on the (unwrapped) C side.
type C_VideoAffineTransformationGetMatrix =
    Ptr GstVideo.VideoAffineTransformationMeta.VideoAffineTransformationMeta ->
    CFloat ->
    IO CInt

-- Args : [Arg {argCName = "meta", argType = TInterface (Name {namespace = "GstVideo", name = "VideoAffineTransformationMeta"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "matrix", argType = TBasicType TFloat, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Nothing, 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 "dynamic" __dynamic_C_VideoAffineTransformationGetMatrix :: FunPtr C_VideoAffineTransformationGetMatrix -> C_VideoAffineTransformationGetMatrix

-- | Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
dynamic_VideoAffineTransformationGetMatrix ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    FunPtr C_VideoAffineTransformationGetMatrix
    -> GstVideo.VideoAffineTransformationMeta.VideoAffineTransformationMeta
    -> Float
    -> m Bool
dynamic_VideoAffineTransformationGetMatrix __funPtr meta matrix = liftIO $ do
    meta' <- unsafeManagedPtrGetPtr meta
    let matrix' = realToFrac matrix
    result <- (__dynamic_C_VideoAffineTransformationGetMatrix __funPtr) meta' matrix'
    let result' = (/= 0) result
    touchManagedPtr meta
    return result'

-- | Generate a function pointer callable from C code, from a `C_VideoAffineTransformationGetMatrix`.
foreign import ccall "wrapper"
    mk_VideoAffineTransformationGetMatrix :: C_VideoAffineTransformationGetMatrix -> IO (FunPtr C_VideoAffineTransformationGetMatrix)

{- |
/No description available in the introspection data./
-}
type VideoAffineTransformationGetMatrix =
    GstVideo.VideoAffineTransformationMeta.VideoAffineTransformationMeta
    -> Float
    -> IO Bool

-- | A convenience synonym for @`Nothing` :: `Maybe` `VideoAffineTransformationGetMatrix`@.
noVideoAffineTransformationGetMatrix :: Maybe VideoAffineTransformationGetMatrix
noVideoAffineTransformationGetMatrix = Nothing

-- | Wrap the callback into a `GClosure`.
genClosure_VideoAffineTransformationGetMatrix :: MonadIO m => VideoAffineTransformationGetMatrix -> m (GClosure C_VideoAffineTransformationGetMatrix)
genClosure_VideoAffineTransformationGetMatrix cb = liftIO $ do
    let cb' = wrap_VideoAffineTransformationGetMatrix Nothing cb
    mk_VideoAffineTransformationGetMatrix cb' >>= B.GClosure.newGClosure


-- | Wrap a `VideoAffineTransformationGetMatrix` into a `C_VideoAffineTransformationGetMatrix`.
wrap_VideoAffineTransformationGetMatrix ::
    Maybe (Ptr (FunPtr C_VideoAffineTransformationGetMatrix)) ->
    VideoAffineTransformationGetMatrix ->
    C_VideoAffineTransformationGetMatrix
wrap_VideoAffineTransformationGetMatrix funptrptr _cb meta matrix = do
    meta' <- (newPtr GstVideo.VideoAffineTransformationMeta.VideoAffineTransformationMeta) meta
    let matrix' = realToFrac matrix
    result <- _cb  meta' matrix'
    maybeReleaseFunPtr funptrptr
    let result' = (fromIntegral . fromEnum) result
    return result'