{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- An opaque video overlay rectangle object. A rectangle contains a single
-- overlay rectangle which can be added to a composition.

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

module GI.GstVideo.Structs.VideoOverlayRectangle
    ( 

-- * Exported types
    VideoOverlayRectangle(..)               ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveVideoOverlayRectangleMethod      ,
#endif


-- ** copy #method:copy#

#if defined(ENABLE_OVERLOADING)
    VideoOverlayRectangleCopyMethodInfo     ,
#endif
    videoOverlayRectangleCopy               ,


-- ** getFlags #method:getFlags#

#if defined(ENABLE_OVERLOADING)
    VideoOverlayRectangleGetFlagsMethodInfo ,
#endif
    videoOverlayRectangleGetFlags           ,


-- ** getGlobalAlpha #method:getGlobalAlpha#

#if defined(ENABLE_OVERLOADING)
    VideoOverlayRectangleGetGlobalAlphaMethodInfo,
#endif
    videoOverlayRectangleGetGlobalAlpha     ,


-- ** getPixelsArgb #method:getPixelsArgb#

#if defined(ENABLE_OVERLOADING)
    VideoOverlayRectangleGetPixelsArgbMethodInfo,
#endif
    videoOverlayRectangleGetPixelsArgb      ,


-- ** getPixelsAyuv #method:getPixelsAyuv#

#if defined(ENABLE_OVERLOADING)
    VideoOverlayRectangleGetPixelsAyuvMethodInfo,
#endif
    videoOverlayRectangleGetPixelsAyuv      ,


-- ** getPixelsRaw #method:getPixelsRaw#

#if defined(ENABLE_OVERLOADING)
    VideoOverlayRectangleGetPixelsRawMethodInfo,
#endif
    videoOverlayRectangleGetPixelsRaw       ,


-- ** getPixelsUnscaledArgb #method:getPixelsUnscaledArgb#

#if defined(ENABLE_OVERLOADING)
    VideoOverlayRectangleGetPixelsUnscaledArgbMethodInfo,
#endif
    videoOverlayRectangleGetPixelsUnscaledArgb,


-- ** getPixelsUnscaledAyuv #method:getPixelsUnscaledAyuv#

#if defined(ENABLE_OVERLOADING)
    VideoOverlayRectangleGetPixelsUnscaledAyuvMethodInfo,
#endif
    videoOverlayRectangleGetPixelsUnscaledAyuv,


-- ** getPixelsUnscaledRaw #method:getPixelsUnscaledRaw#

#if defined(ENABLE_OVERLOADING)
    VideoOverlayRectangleGetPixelsUnscaledRawMethodInfo,
#endif
    videoOverlayRectangleGetPixelsUnscaledRaw,


-- ** getRenderRectangle #method:getRenderRectangle#

#if defined(ENABLE_OVERLOADING)
    VideoOverlayRectangleGetRenderRectangleMethodInfo,
#endif
    videoOverlayRectangleGetRenderRectangle ,


-- ** getSeqnum #method:getSeqnum#

#if defined(ENABLE_OVERLOADING)
    VideoOverlayRectangleGetSeqnumMethodInfo,
#endif
    videoOverlayRectangleGetSeqnum          ,


-- ** newRaw #method:newRaw#

    videoOverlayRectangleNewRaw             ,


-- ** setGlobalAlpha #method:setGlobalAlpha#

#if defined(ENABLE_OVERLOADING)
    VideoOverlayRectangleSetGlobalAlphaMethodInfo,
#endif
    videoOverlayRectangleSetGlobalAlpha     ,


-- ** setRenderRectangle #method:setRenderRectangle#

#if defined(ENABLE_OVERLOADING)
    VideoOverlayRectangleSetRenderRectangleMethodInfo,
#endif
    videoOverlayRectangleSetRenderRectangle ,




    ) 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.BasicTypes as B.Types
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.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
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.Structs.Buffer as Gst.Buffer
import {-# SOURCE #-} qualified GI.GstVideo.Flags as GstVideo.Flags

-- | Memory-managed wrapper type.
newtype VideoOverlayRectangle = VideoOverlayRectangle (SP.ManagedPtr VideoOverlayRectangle)
    deriving (VideoOverlayRectangle -> VideoOverlayRectangle -> Bool
(VideoOverlayRectangle -> VideoOverlayRectangle -> Bool)
-> (VideoOverlayRectangle -> VideoOverlayRectangle -> Bool)
-> Eq VideoOverlayRectangle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VideoOverlayRectangle -> VideoOverlayRectangle -> Bool
$c/= :: VideoOverlayRectangle -> VideoOverlayRectangle -> Bool
== :: VideoOverlayRectangle -> VideoOverlayRectangle -> Bool
$c== :: VideoOverlayRectangle -> VideoOverlayRectangle -> Bool
Eq)

instance SP.ManagedPtrNewtype VideoOverlayRectangle where
    toManagedPtr :: VideoOverlayRectangle -> ManagedPtr VideoOverlayRectangle
toManagedPtr (VideoOverlayRectangle ManagedPtr VideoOverlayRectangle
p) = ManagedPtr VideoOverlayRectangle
p

foreign import ccall "gst_video_overlay_rectangle_get_type" c_gst_video_overlay_rectangle_get_type :: 
    IO GType

type instance O.ParentTypes VideoOverlayRectangle = '[]
instance O.HasParentTypes VideoOverlayRectangle

instance B.Types.TypedObject VideoOverlayRectangle where
    glibType :: IO GType
glibType = IO GType
c_gst_video_overlay_rectangle_get_type

instance B.Types.GBoxed VideoOverlayRectangle

-- | Convert 'VideoOverlayRectangle' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue VideoOverlayRectangle where
    toGValue :: VideoOverlayRectangle -> IO GValue
toGValue VideoOverlayRectangle
o = do
        GType
gtype <- IO GType
c_gst_video_overlay_rectangle_get_type
        VideoOverlayRectangle
-> (Ptr VideoOverlayRectangle -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr VideoOverlayRectangle
o (GType
-> (GValue -> Ptr VideoOverlayRectangle -> IO ())
-> Ptr VideoOverlayRectangle
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr VideoOverlayRectangle -> IO ()
forall a. GValue -> Ptr a -> IO ()
B.GValue.set_boxed)
        
    fromGValue :: GValue -> IO VideoOverlayRectangle
fromGValue GValue
gv = do
        Ptr VideoOverlayRectangle
ptr <- GValue -> IO (Ptr VideoOverlayRectangle)
forall b. GValue -> IO (Ptr b)
B.GValue.get_boxed GValue
gv :: IO (Ptr VideoOverlayRectangle)
        (ManagedPtr VideoOverlayRectangle -> VideoOverlayRectangle)
-> Ptr VideoOverlayRectangle -> IO VideoOverlayRectangle
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr VideoOverlayRectangle -> VideoOverlayRectangle
VideoOverlayRectangle Ptr VideoOverlayRectangle
ptr
        
    


#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList VideoOverlayRectangle
type instance O.AttributeList VideoOverlayRectangle = VideoOverlayRectangleAttributeList
type VideoOverlayRectangleAttributeList = ('[ ] :: [(Symbol, *)])
#endif

-- method VideoOverlayRectangle::new_raw
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "pixels"
--           , argType = TInterface Name { namespace = "Gst" , name = "Buffer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstBuffer pointing to the pixel memory"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "render_x"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the X co-ordinate on the video where the top-left corner of this\n    overlay rectangle should be rendered to"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "render_y"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the Y co-ordinate on the video where the top-left corner of this\n    overlay rectangle should be rendered to"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "render_width"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the render width of this rectangle on the video"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "render_height"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the render height of this rectangle on the video"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface
--                 Name { namespace = "GstVideo" , name = "VideoOverlayFormatFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "flags" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "GstVideo" , name = "VideoOverlayRectangle" })
-- throws : False
-- Skip return : False

foreign import ccall "gst_video_overlay_rectangle_new_raw" gst_video_overlay_rectangle_new_raw :: 
    Ptr Gst.Buffer.Buffer ->                -- pixels : TInterface (Name {namespace = "Gst", name = "Buffer"})
    Int32 ->                                -- render_x : TBasicType TInt
    Int32 ->                                -- render_y : TBasicType TInt
    Word32 ->                               -- render_width : TBasicType TUInt
    Word32 ->                               -- render_height : TBasicType TUInt
    CUInt ->                                -- flags : TInterface (Name {namespace = "GstVideo", name = "VideoOverlayFormatFlags"})
    IO (Ptr VideoOverlayRectangle)

-- | Creates a new video overlay rectangle with ARGB or AYUV pixel data.
-- The layout in case of ARGB of the components in memory is B-G-R-A
-- on little-endian platforms
-- (corresponding to @/GST_VIDEO_FORMAT_BGRA/@) and A-R-G-B on big-endian
-- platforms (corresponding to @/GST_VIDEO_FORMAT_ARGB/@). In other words,
-- pixels are treated as 32-bit words and the lowest 8 bits then contain
-- the blue component value and the highest 8 bits contain the alpha
-- component value. Unless specified in the flags, the RGB values are
-- non-premultiplied. This is the format that is used by most hardware,
-- and also many rendering libraries such as Cairo, for example.
-- The pixel data buffer must have t'GI.GstVideo.Structs.VideoMeta.VideoMeta' set.
videoOverlayRectangleNewRaw ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Gst.Buffer.Buffer
    -- ^ /@pixels@/: a t'GI.Gst.Structs.Buffer.Buffer' pointing to the pixel memory
    -> Int32
    -- ^ /@renderX@/: the X co-ordinate on the video where the top-left corner of this
    --     overlay rectangle should be rendered to
    -> Int32
    -- ^ /@renderY@/: the Y co-ordinate on the video where the top-left corner of this
    --     overlay rectangle should be rendered to
    -> Word32
    -- ^ /@renderWidth@/: the render width of this rectangle on the video
    -> Word32
    -- ^ /@renderHeight@/: the render height of this rectangle on the video
    -> [GstVideo.Flags.VideoOverlayFormatFlags]
    -- ^ /@flags@/: flags
    -> m VideoOverlayRectangle
    -- ^ __Returns:__ a new t'GI.GstVideo.Structs.VideoOverlayRectangle.VideoOverlayRectangle'. Unref with
    --     @/gst_video_overlay_rectangle_unref()/@ when no longer needed.
videoOverlayRectangleNewRaw :: Buffer
-> Int32
-> Int32
-> Word32
-> Word32
-> [VideoOverlayFormatFlags]
-> m VideoOverlayRectangle
videoOverlayRectangleNewRaw Buffer
pixels Int32
renderX Int32
renderY Word32
renderWidth Word32
renderHeight [VideoOverlayFormatFlags]
flags = IO VideoOverlayRectangle -> m VideoOverlayRectangle
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO VideoOverlayRectangle -> m VideoOverlayRectangle)
-> IO VideoOverlayRectangle -> m VideoOverlayRectangle
forall a b. (a -> b) -> a -> b
$ do
    Ptr Buffer
pixels' <- Buffer -> IO (Ptr Buffer)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Buffer
pixels
    let flags' :: CUInt
flags' = [VideoOverlayFormatFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [VideoOverlayFormatFlags]
flags
    Ptr VideoOverlayRectangle
result <- Ptr Buffer
-> Int32
-> Int32
-> Word32
-> Word32
-> CUInt
-> IO (Ptr VideoOverlayRectangle)
gst_video_overlay_rectangle_new_raw Ptr Buffer
pixels' Int32
renderX Int32
renderY Word32
renderWidth Word32
renderHeight CUInt
flags'
    Text -> Ptr VideoOverlayRectangle -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"videoOverlayRectangleNewRaw" Ptr VideoOverlayRectangle
result
    VideoOverlayRectangle
result' <- ((ManagedPtr VideoOverlayRectangle -> VideoOverlayRectangle)
-> Ptr VideoOverlayRectangle -> IO VideoOverlayRectangle
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr VideoOverlayRectangle -> VideoOverlayRectangle
VideoOverlayRectangle) Ptr VideoOverlayRectangle
result
    Buffer -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Buffer
pixels
    VideoOverlayRectangle -> IO VideoOverlayRectangle
forall (m :: * -> *) a. Monad m => a -> m a
return VideoOverlayRectangle
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method VideoOverlayRectangle::copy
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "rectangle"
--           , argType =
--               TInterface
--                 Name { namespace = "GstVideo" , name = "VideoOverlayRectangle" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstVideoOverlayRectangle to copy"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "GstVideo" , name = "VideoOverlayRectangle" })
-- throws : False
-- Skip return : False

foreign import ccall "gst_video_overlay_rectangle_copy" gst_video_overlay_rectangle_copy :: 
    Ptr VideoOverlayRectangle ->            -- rectangle : TInterface (Name {namespace = "GstVideo", name = "VideoOverlayRectangle"})
    IO (Ptr VideoOverlayRectangle)

-- | Makes a copy of /@rectangle@/, so that it is possible to modify it
-- (e.g. to change the render co-ordinates or render dimension). The
-- actual overlay pixel data buffers contained in the rectangle are not
-- copied.
videoOverlayRectangleCopy ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VideoOverlayRectangle
    -- ^ /@rectangle@/: a t'GI.GstVideo.Structs.VideoOverlayRectangle.VideoOverlayRectangle' to copy
    -> m VideoOverlayRectangle
    -- ^ __Returns:__ a new t'GI.GstVideo.Structs.VideoOverlayRectangle.VideoOverlayRectangle' equivalent
    --     to /@rectangle@/.
videoOverlayRectangleCopy :: VideoOverlayRectangle -> m VideoOverlayRectangle
videoOverlayRectangleCopy VideoOverlayRectangle
rectangle = IO VideoOverlayRectangle -> m VideoOverlayRectangle
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO VideoOverlayRectangle -> m VideoOverlayRectangle)
-> IO VideoOverlayRectangle -> m VideoOverlayRectangle
forall a b. (a -> b) -> a -> b
$ do
    Ptr VideoOverlayRectangle
rectangle' <- VideoOverlayRectangle -> IO (Ptr VideoOverlayRectangle)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr VideoOverlayRectangle
rectangle
    Ptr VideoOverlayRectangle
result <- Ptr VideoOverlayRectangle -> IO (Ptr VideoOverlayRectangle)
gst_video_overlay_rectangle_copy Ptr VideoOverlayRectangle
rectangle'
    Text -> Ptr VideoOverlayRectangle -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"videoOverlayRectangleCopy" Ptr VideoOverlayRectangle
result
    VideoOverlayRectangle
result' <- ((ManagedPtr VideoOverlayRectangle -> VideoOverlayRectangle)
-> Ptr VideoOverlayRectangle -> IO VideoOverlayRectangle
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr VideoOverlayRectangle -> VideoOverlayRectangle
VideoOverlayRectangle) Ptr VideoOverlayRectangle
result
    VideoOverlayRectangle -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr VideoOverlayRectangle
rectangle
    VideoOverlayRectangle -> IO VideoOverlayRectangle
forall (m :: * -> *) a. Monad m => a -> m a
return VideoOverlayRectangle
result'

#if defined(ENABLE_OVERLOADING)
data VideoOverlayRectangleCopyMethodInfo
instance (signature ~ (m VideoOverlayRectangle), MonadIO m) => O.MethodInfo VideoOverlayRectangleCopyMethodInfo VideoOverlayRectangle signature where
    overloadedMethod = videoOverlayRectangleCopy

#endif

-- method VideoOverlayRectangle::get_flags
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "rectangle"
--           , argType =
--               TInterface
--                 Name { namespace = "GstVideo" , name = "VideoOverlayRectangle" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstVideoOverlayRectangle"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "GstVideo" , name = "VideoOverlayFormatFlags" })
-- throws : False
-- Skip return : False

foreign import ccall "gst_video_overlay_rectangle_get_flags" gst_video_overlay_rectangle_get_flags :: 
    Ptr VideoOverlayRectangle ->            -- rectangle : TInterface (Name {namespace = "GstVideo", name = "VideoOverlayRectangle"})
    IO CUInt

-- | Retrieves the flags associated with a t'GI.GstVideo.Structs.VideoOverlayRectangle.VideoOverlayRectangle'.
-- This is useful if the caller can handle both premultiplied alpha and
-- non premultiplied alpha, for example. By knowing whether the rectangle
-- uses premultiplied or not, it can request the pixel data in the format
-- it is stored in, to avoid unnecessary conversion.
videoOverlayRectangleGetFlags ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VideoOverlayRectangle
    -- ^ /@rectangle@/: a t'GI.GstVideo.Structs.VideoOverlayRectangle.VideoOverlayRectangle'
    -> m [GstVideo.Flags.VideoOverlayFormatFlags]
    -- ^ __Returns:__ the t'GI.GstVideo.Flags.VideoOverlayFormatFlags' associated with the rectangle.
videoOverlayRectangleGetFlags :: VideoOverlayRectangle -> m [VideoOverlayFormatFlags]
videoOverlayRectangleGetFlags VideoOverlayRectangle
rectangle = IO [VideoOverlayFormatFlags] -> m [VideoOverlayFormatFlags]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [VideoOverlayFormatFlags] -> m [VideoOverlayFormatFlags])
-> IO [VideoOverlayFormatFlags] -> m [VideoOverlayFormatFlags]
forall a b. (a -> b) -> a -> b
$ do
    Ptr VideoOverlayRectangle
rectangle' <- VideoOverlayRectangle -> IO (Ptr VideoOverlayRectangle)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr VideoOverlayRectangle
rectangle
    CUInt
result <- Ptr VideoOverlayRectangle -> IO CUInt
gst_video_overlay_rectangle_get_flags Ptr VideoOverlayRectangle
rectangle'
    let result' :: [VideoOverlayFormatFlags]
result' = CUInt -> [VideoOverlayFormatFlags]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
    VideoOverlayRectangle -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr VideoOverlayRectangle
rectangle
    [VideoOverlayFormatFlags] -> IO [VideoOverlayFormatFlags]
forall (m :: * -> *) a. Monad m => a -> m a
return [VideoOverlayFormatFlags]
result'

#if defined(ENABLE_OVERLOADING)
data VideoOverlayRectangleGetFlagsMethodInfo
instance (signature ~ (m [GstVideo.Flags.VideoOverlayFormatFlags]), MonadIO m) => O.MethodInfo VideoOverlayRectangleGetFlagsMethodInfo VideoOverlayRectangle signature where
    overloadedMethod = videoOverlayRectangleGetFlags

#endif

-- method VideoOverlayRectangle::get_global_alpha
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "rectangle"
--           , argType =
--               TInterface
--                 Name { namespace = "GstVideo" , name = "VideoOverlayRectangle" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstVideoOverlayRectangle"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TFloat)
-- throws : False
-- Skip return : False

foreign import ccall "gst_video_overlay_rectangle_get_global_alpha" gst_video_overlay_rectangle_get_global_alpha :: 
    Ptr VideoOverlayRectangle ->            -- rectangle : TInterface (Name {namespace = "GstVideo", name = "VideoOverlayRectangle"})
    IO CFloat

-- | Retrieves the global-alpha value associated with a t'GI.GstVideo.Structs.VideoOverlayRectangle.VideoOverlayRectangle'.
videoOverlayRectangleGetGlobalAlpha ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VideoOverlayRectangle
    -- ^ /@rectangle@/: a t'GI.GstVideo.Structs.VideoOverlayRectangle.VideoOverlayRectangle'
    -> m Float
    -- ^ __Returns:__ the global-alpha value associated with the rectangle.
videoOverlayRectangleGetGlobalAlpha :: VideoOverlayRectangle -> m Float
videoOverlayRectangleGetGlobalAlpha VideoOverlayRectangle
rectangle = IO Float -> m Float
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ do
    Ptr VideoOverlayRectangle
rectangle' <- VideoOverlayRectangle -> IO (Ptr VideoOverlayRectangle)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr VideoOverlayRectangle
rectangle
    CFloat
result <- Ptr VideoOverlayRectangle -> IO CFloat
gst_video_overlay_rectangle_get_global_alpha Ptr VideoOverlayRectangle
rectangle'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    VideoOverlayRectangle -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr VideoOverlayRectangle
rectangle
    Float -> IO Float
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'

#if defined(ENABLE_OVERLOADING)
data VideoOverlayRectangleGetGlobalAlphaMethodInfo
instance (signature ~ (m Float), MonadIO m) => O.MethodInfo VideoOverlayRectangleGetGlobalAlphaMethodInfo VideoOverlayRectangle signature where
    overloadedMethod = videoOverlayRectangleGetGlobalAlpha

#endif

-- method VideoOverlayRectangle::get_pixels_argb
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "rectangle"
--           , argType =
--               TInterface
--                 Name { namespace = "GstVideo" , name = "VideoOverlayRectangle" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstVideoOverlayRectangle"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface
--                 Name { namespace = "GstVideo" , name = "VideoOverlayFormatFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "flags\n   If a global_alpha value != 1 is set for the rectangle, the caller\n   should set the #GST_VIDEO_OVERLAY_FORMAT_FLAG_GLOBAL_ALPHA flag\n   if he wants to apply global-alpha himself. If the flag is not set\n   global_alpha is applied internally before returning the pixel-data."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gst" , name = "Buffer" })
-- throws : False
-- Skip return : False

foreign import ccall "gst_video_overlay_rectangle_get_pixels_argb" gst_video_overlay_rectangle_get_pixels_argb :: 
    Ptr VideoOverlayRectangle ->            -- rectangle : TInterface (Name {namespace = "GstVideo", name = "VideoOverlayRectangle"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "GstVideo", name = "VideoOverlayFormatFlags"})
    IO (Ptr Gst.Buffer.Buffer)

-- | /No description available in the introspection data./
videoOverlayRectangleGetPixelsArgb ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VideoOverlayRectangle
    -- ^ /@rectangle@/: a t'GI.GstVideo.Structs.VideoOverlayRectangle.VideoOverlayRectangle'
    -> [GstVideo.Flags.VideoOverlayFormatFlags]
    -- ^ /@flags@/: flags
    --    If a global_alpha value != 1 is set for the rectangle, the caller
    --    should set the @/GST_VIDEO_OVERLAY_FORMAT_FLAG_GLOBAL_ALPHA/@ flag
    --    if he wants to apply global-alpha himself. If the flag is not set
    --    global_alpha is applied internally before returning the pixel-data.
    -> m Gst.Buffer.Buffer
    -- ^ __Returns:__ a t'GI.Gst.Structs.Buffer.Buffer' holding the ARGB pixel data with
    --    width and height of the render dimensions as per
    --    'GI.GstVideo.Structs.VideoOverlayRectangle.videoOverlayRectangleGetRenderRectangle'. This function does
    --    not return a reference, the caller should obtain a reference of her own
    --    with @/gst_buffer_ref()/@ if needed.
videoOverlayRectangleGetPixelsArgb :: VideoOverlayRectangle -> [VideoOverlayFormatFlags] -> m Buffer
videoOverlayRectangleGetPixelsArgb VideoOverlayRectangle
rectangle [VideoOverlayFormatFlags]
flags = IO Buffer -> m Buffer
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Buffer -> m Buffer) -> IO Buffer -> m Buffer
forall a b. (a -> b) -> a -> b
$ do
    Ptr VideoOverlayRectangle
rectangle' <- VideoOverlayRectangle -> IO (Ptr VideoOverlayRectangle)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr VideoOverlayRectangle
rectangle
    let flags' :: CUInt
flags' = [VideoOverlayFormatFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [VideoOverlayFormatFlags]
flags
    Ptr Buffer
result <- Ptr VideoOverlayRectangle -> CUInt -> IO (Ptr Buffer)
gst_video_overlay_rectangle_get_pixels_argb Ptr VideoOverlayRectangle
rectangle' CUInt
flags'
    Text -> Ptr Buffer -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"videoOverlayRectangleGetPixelsArgb" Ptr Buffer
result
    Buffer
result' <- ((ManagedPtr Buffer -> Buffer) -> Ptr Buffer -> IO Buffer
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Buffer -> Buffer
Gst.Buffer.Buffer) Ptr Buffer
result
    VideoOverlayRectangle -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr VideoOverlayRectangle
rectangle
    Buffer -> IO Buffer
forall (m :: * -> *) a. Monad m => a -> m a
return Buffer
result'

#if defined(ENABLE_OVERLOADING)
data VideoOverlayRectangleGetPixelsArgbMethodInfo
instance (signature ~ ([GstVideo.Flags.VideoOverlayFormatFlags] -> m Gst.Buffer.Buffer), MonadIO m) => O.MethodInfo VideoOverlayRectangleGetPixelsArgbMethodInfo VideoOverlayRectangle signature where
    overloadedMethod = videoOverlayRectangleGetPixelsArgb

#endif

-- method VideoOverlayRectangle::get_pixels_ayuv
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "rectangle"
--           , argType =
--               TInterface
--                 Name { namespace = "GstVideo" , name = "VideoOverlayRectangle" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstVideoOverlayRectangle"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface
--                 Name { namespace = "GstVideo" , name = "VideoOverlayFormatFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "flags\n   If a global_alpha value != 1 is set for the rectangle, the caller\n   should set the #GST_VIDEO_OVERLAY_FORMAT_FLAG_GLOBAL_ALPHA flag\n   if he wants to apply global-alpha himself. If the flag is not set\n   global_alpha is applied internally before returning the pixel-data."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gst" , name = "Buffer" })
-- throws : False
-- Skip return : False

foreign import ccall "gst_video_overlay_rectangle_get_pixels_ayuv" gst_video_overlay_rectangle_get_pixels_ayuv :: 
    Ptr VideoOverlayRectangle ->            -- rectangle : TInterface (Name {namespace = "GstVideo", name = "VideoOverlayRectangle"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "GstVideo", name = "VideoOverlayFormatFlags"})
    IO (Ptr Gst.Buffer.Buffer)

-- | /No description available in the introspection data./
videoOverlayRectangleGetPixelsAyuv ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VideoOverlayRectangle
    -- ^ /@rectangle@/: a t'GI.GstVideo.Structs.VideoOverlayRectangle.VideoOverlayRectangle'
    -> [GstVideo.Flags.VideoOverlayFormatFlags]
    -- ^ /@flags@/: flags
    --    If a global_alpha value != 1 is set for the rectangle, the caller
    --    should set the @/GST_VIDEO_OVERLAY_FORMAT_FLAG_GLOBAL_ALPHA/@ flag
    --    if he wants to apply global-alpha himself. If the flag is not set
    --    global_alpha is applied internally before returning the pixel-data.
    -> m Gst.Buffer.Buffer
    -- ^ __Returns:__ a t'GI.Gst.Structs.Buffer.Buffer' holding the AYUV pixel data with
    --    width and height of the render dimensions as per
    --    'GI.GstVideo.Structs.VideoOverlayRectangle.videoOverlayRectangleGetRenderRectangle'. This function does
    --    not return a reference, the caller should obtain a reference of her own
    --    with @/gst_buffer_ref()/@ if needed.
videoOverlayRectangleGetPixelsAyuv :: VideoOverlayRectangle -> [VideoOverlayFormatFlags] -> m Buffer
videoOverlayRectangleGetPixelsAyuv VideoOverlayRectangle
rectangle [VideoOverlayFormatFlags]
flags = IO Buffer -> m Buffer
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Buffer -> m Buffer) -> IO Buffer -> m Buffer
forall a b. (a -> b) -> a -> b
$ do
    Ptr VideoOverlayRectangle
rectangle' <- VideoOverlayRectangle -> IO (Ptr VideoOverlayRectangle)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr VideoOverlayRectangle
rectangle
    let flags' :: CUInt
flags' = [VideoOverlayFormatFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [VideoOverlayFormatFlags]
flags
    Ptr Buffer
result <- Ptr VideoOverlayRectangle -> CUInt -> IO (Ptr Buffer)
gst_video_overlay_rectangle_get_pixels_ayuv Ptr VideoOverlayRectangle
rectangle' CUInt
flags'
    Text -> Ptr Buffer -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"videoOverlayRectangleGetPixelsAyuv" Ptr Buffer
result
    Buffer
result' <- ((ManagedPtr Buffer -> Buffer) -> Ptr Buffer -> IO Buffer
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Buffer -> Buffer
Gst.Buffer.Buffer) Ptr Buffer
result
    VideoOverlayRectangle -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr VideoOverlayRectangle
rectangle
    Buffer -> IO Buffer
forall (m :: * -> *) a. Monad m => a -> m a
return Buffer
result'

#if defined(ENABLE_OVERLOADING)
data VideoOverlayRectangleGetPixelsAyuvMethodInfo
instance (signature ~ ([GstVideo.Flags.VideoOverlayFormatFlags] -> m Gst.Buffer.Buffer), MonadIO m) => O.MethodInfo VideoOverlayRectangleGetPixelsAyuvMethodInfo VideoOverlayRectangle signature where
    overloadedMethod = videoOverlayRectangleGetPixelsAyuv

#endif

-- method VideoOverlayRectangle::get_pixels_raw
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "rectangle"
--           , argType =
--               TInterface
--                 Name { namespace = "GstVideo" , name = "VideoOverlayRectangle" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstVideoOverlayRectangle"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface
--                 Name { namespace = "GstVideo" , name = "VideoOverlayFormatFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "flags\n   If a global_alpha value != 1 is set for the rectangle, the caller\n   should set the #GST_VIDEO_OVERLAY_FORMAT_FLAG_GLOBAL_ALPHA flag\n   if he wants to apply global-alpha himself. If the flag is not set\n   global_alpha is applied internally before returning the pixel-data."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gst" , name = "Buffer" })
-- throws : False
-- Skip return : False

foreign import ccall "gst_video_overlay_rectangle_get_pixels_raw" gst_video_overlay_rectangle_get_pixels_raw :: 
    Ptr VideoOverlayRectangle ->            -- rectangle : TInterface (Name {namespace = "GstVideo", name = "VideoOverlayRectangle"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "GstVideo", name = "VideoOverlayFormatFlags"})
    IO (Ptr Gst.Buffer.Buffer)

-- | /No description available in the introspection data./
videoOverlayRectangleGetPixelsRaw ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VideoOverlayRectangle
    -- ^ /@rectangle@/: a t'GI.GstVideo.Structs.VideoOverlayRectangle.VideoOverlayRectangle'
    -> [GstVideo.Flags.VideoOverlayFormatFlags]
    -- ^ /@flags@/: flags
    --    If a global_alpha value != 1 is set for the rectangle, the caller
    --    should set the @/GST_VIDEO_OVERLAY_FORMAT_FLAG_GLOBAL_ALPHA/@ flag
    --    if he wants to apply global-alpha himself. If the flag is not set
    --    global_alpha is applied internally before returning the pixel-data.
    -> m Gst.Buffer.Buffer
    -- ^ __Returns:__ a t'GI.Gst.Structs.Buffer.Buffer' holding the pixel data with
    --    format as originally provided and specified in video meta with
    --    width and height of the render dimensions as per
    --    'GI.GstVideo.Structs.VideoOverlayRectangle.videoOverlayRectangleGetRenderRectangle'. This function does
    --    not return a reference, the caller should obtain a reference of her own
    --    with @/gst_buffer_ref()/@ if needed.
videoOverlayRectangleGetPixelsRaw :: VideoOverlayRectangle -> [VideoOverlayFormatFlags] -> m Buffer
videoOverlayRectangleGetPixelsRaw VideoOverlayRectangle
rectangle [VideoOverlayFormatFlags]
flags = IO Buffer -> m Buffer
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Buffer -> m Buffer) -> IO Buffer -> m Buffer
forall a b. (a -> b) -> a -> b
$ do
    Ptr VideoOverlayRectangle
rectangle' <- VideoOverlayRectangle -> IO (Ptr VideoOverlayRectangle)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr VideoOverlayRectangle
rectangle
    let flags' :: CUInt
flags' = [VideoOverlayFormatFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [VideoOverlayFormatFlags]
flags
    Ptr Buffer
result <- Ptr VideoOverlayRectangle -> CUInt -> IO (Ptr Buffer)
gst_video_overlay_rectangle_get_pixels_raw Ptr VideoOverlayRectangle
rectangle' CUInt
flags'
    Text -> Ptr Buffer -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"videoOverlayRectangleGetPixelsRaw" Ptr Buffer
result
    Buffer
result' <- ((ManagedPtr Buffer -> Buffer) -> Ptr Buffer -> IO Buffer
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Buffer -> Buffer
Gst.Buffer.Buffer) Ptr Buffer
result
    VideoOverlayRectangle -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr VideoOverlayRectangle
rectangle
    Buffer -> IO Buffer
forall (m :: * -> *) a. Monad m => a -> m a
return Buffer
result'

#if defined(ENABLE_OVERLOADING)
data VideoOverlayRectangleGetPixelsRawMethodInfo
instance (signature ~ ([GstVideo.Flags.VideoOverlayFormatFlags] -> m Gst.Buffer.Buffer), MonadIO m) => O.MethodInfo VideoOverlayRectangleGetPixelsRawMethodInfo VideoOverlayRectangle signature where
    overloadedMethod = videoOverlayRectangleGetPixelsRaw

#endif

-- method VideoOverlayRectangle::get_pixels_unscaled_argb
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "rectangle"
--           , argType =
--               TInterface
--                 Name { namespace = "GstVideo" , name = "VideoOverlayRectangle" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstVideoOverlayRectangle"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface
--                 Name { namespace = "GstVideo" , name = "VideoOverlayFormatFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "flags.\n   If a global_alpha value != 1 is set for the rectangle, the caller\n   should set the #GST_VIDEO_OVERLAY_FORMAT_FLAG_GLOBAL_ALPHA flag\n   if he wants to apply global-alpha himself. If the flag is not set\n   global_alpha is applied internally before returning the pixel-data."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gst" , name = "Buffer" })
-- throws : False
-- Skip return : False

foreign import ccall "gst_video_overlay_rectangle_get_pixels_unscaled_argb" gst_video_overlay_rectangle_get_pixels_unscaled_argb :: 
    Ptr VideoOverlayRectangle ->            -- rectangle : TInterface (Name {namespace = "GstVideo", name = "VideoOverlayRectangle"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "GstVideo", name = "VideoOverlayFormatFlags"})
    IO (Ptr Gst.Buffer.Buffer)

-- | Retrieves the pixel data as it is. This is useful if the caller can
-- do the scaling itself when handling the overlaying. The rectangle will
-- need to be scaled to the render dimensions, which can be retrieved using
-- 'GI.GstVideo.Structs.VideoOverlayRectangle.videoOverlayRectangleGetRenderRectangle'.
videoOverlayRectangleGetPixelsUnscaledArgb ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VideoOverlayRectangle
    -- ^ /@rectangle@/: a t'GI.GstVideo.Structs.VideoOverlayRectangle.VideoOverlayRectangle'
    -> [GstVideo.Flags.VideoOverlayFormatFlags]
    -- ^ /@flags@/: flags.
    --    If a global_alpha value != 1 is set for the rectangle, the caller
    --    should set the @/GST_VIDEO_OVERLAY_FORMAT_FLAG_GLOBAL_ALPHA/@ flag
    --    if he wants to apply global-alpha himself. If the flag is not set
    --    global_alpha is applied internally before returning the pixel-data.
    -> m Gst.Buffer.Buffer
    -- ^ __Returns:__ a t'GI.Gst.Structs.Buffer.Buffer' holding the ARGB pixel data with
    --    t'GI.GstVideo.Structs.VideoMeta.VideoMeta' set. This function does not return a reference, the caller
    --    should obtain a reference of her own with @/gst_buffer_ref()/@ if needed.
videoOverlayRectangleGetPixelsUnscaledArgb :: VideoOverlayRectangle -> [VideoOverlayFormatFlags] -> m Buffer
videoOverlayRectangleGetPixelsUnscaledArgb VideoOverlayRectangle
rectangle [VideoOverlayFormatFlags]
flags = IO Buffer -> m Buffer
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Buffer -> m Buffer) -> IO Buffer -> m Buffer
forall a b. (a -> b) -> a -> b
$ do
    Ptr VideoOverlayRectangle
rectangle' <- VideoOverlayRectangle -> IO (Ptr VideoOverlayRectangle)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr VideoOverlayRectangle
rectangle
    let flags' :: CUInt
flags' = [VideoOverlayFormatFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [VideoOverlayFormatFlags]
flags
    Ptr Buffer
result <- Ptr VideoOverlayRectangle -> CUInt -> IO (Ptr Buffer)
gst_video_overlay_rectangle_get_pixels_unscaled_argb Ptr VideoOverlayRectangle
rectangle' CUInt
flags'
    Text -> Ptr Buffer -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"videoOverlayRectangleGetPixelsUnscaledArgb" Ptr Buffer
result
    Buffer
result' <- ((ManagedPtr Buffer -> Buffer) -> Ptr Buffer -> IO Buffer
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Buffer -> Buffer
Gst.Buffer.Buffer) Ptr Buffer
result
    VideoOverlayRectangle -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr VideoOverlayRectangle
rectangle
    Buffer -> IO Buffer
forall (m :: * -> *) a. Monad m => a -> m a
return Buffer
result'

#if defined(ENABLE_OVERLOADING)
data VideoOverlayRectangleGetPixelsUnscaledArgbMethodInfo
instance (signature ~ ([GstVideo.Flags.VideoOverlayFormatFlags] -> m Gst.Buffer.Buffer), MonadIO m) => O.MethodInfo VideoOverlayRectangleGetPixelsUnscaledArgbMethodInfo VideoOverlayRectangle signature where
    overloadedMethod = videoOverlayRectangleGetPixelsUnscaledArgb

#endif

-- method VideoOverlayRectangle::get_pixels_unscaled_ayuv
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "rectangle"
--           , argType =
--               TInterface
--                 Name { namespace = "GstVideo" , name = "VideoOverlayRectangle" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstVideoOverlayRectangle"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface
--                 Name { namespace = "GstVideo" , name = "VideoOverlayFormatFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "flags.\n   If a global_alpha value != 1 is set for the rectangle, the caller\n   should set the #GST_VIDEO_OVERLAY_FORMAT_FLAG_GLOBAL_ALPHA flag\n   if he wants to apply global-alpha himself. If the flag is not set\n   global_alpha is applied internally before returning the pixel-data."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gst" , name = "Buffer" })
-- throws : False
-- Skip return : False

foreign import ccall "gst_video_overlay_rectangle_get_pixels_unscaled_ayuv" gst_video_overlay_rectangle_get_pixels_unscaled_ayuv :: 
    Ptr VideoOverlayRectangle ->            -- rectangle : TInterface (Name {namespace = "GstVideo", name = "VideoOverlayRectangle"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "GstVideo", name = "VideoOverlayFormatFlags"})
    IO (Ptr Gst.Buffer.Buffer)

-- | Retrieves the pixel data as it is. This is useful if the caller can
-- do the scaling itself when handling the overlaying. The rectangle will
-- need to be scaled to the render dimensions, which can be retrieved using
-- 'GI.GstVideo.Structs.VideoOverlayRectangle.videoOverlayRectangleGetRenderRectangle'.
videoOverlayRectangleGetPixelsUnscaledAyuv ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VideoOverlayRectangle
    -- ^ /@rectangle@/: a t'GI.GstVideo.Structs.VideoOverlayRectangle.VideoOverlayRectangle'
    -> [GstVideo.Flags.VideoOverlayFormatFlags]
    -- ^ /@flags@/: flags.
    --    If a global_alpha value != 1 is set for the rectangle, the caller
    --    should set the @/GST_VIDEO_OVERLAY_FORMAT_FLAG_GLOBAL_ALPHA/@ flag
    --    if he wants to apply global-alpha himself. If the flag is not set
    --    global_alpha is applied internally before returning the pixel-data.
    -> m Gst.Buffer.Buffer
    -- ^ __Returns:__ a t'GI.Gst.Structs.Buffer.Buffer' holding the AYUV pixel data with
    --    t'GI.GstVideo.Structs.VideoMeta.VideoMeta' set. This function does not return a reference, the caller
    --    should obtain a reference of her own with @/gst_buffer_ref()/@ if needed.
videoOverlayRectangleGetPixelsUnscaledAyuv :: VideoOverlayRectangle -> [VideoOverlayFormatFlags] -> m Buffer
videoOverlayRectangleGetPixelsUnscaledAyuv VideoOverlayRectangle
rectangle [VideoOverlayFormatFlags]
flags = IO Buffer -> m Buffer
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Buffer -> m Buffer) -> IO Buffer -> m Buffer
forall a b. (a -> b) -> a -> b
$ do
    Ptr VideoOverlayRectangle
rectangle' <- VideoOverlayRectangle -> IO (Ptr VideoOverlayRectangle)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr VideoOverlayRectangle
rectangle
    let flags' :: CUInt
flags' = [VideoOverlayFormatFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [VideoOverlayFormatFlags]
flags
    Ptr Buffer
result <- Ptr VideoOverlayRectangle -> CUInt -> IO (Ptr Buffer)
gst_video_overlay_rectangle_get_pixels_unscaled_ayuv Ptr VideoOverlayRectangle
rectangle' CUInt
flags'
    Text -> Ptr Buffer -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"videoOverlayRectangleGetPixelsUnscaledAyuv" Ptr Buffer
result
    Buffer
result' <- ((ManagedPtr Buffer -> Buffer) -> Ptr Buffer -> IO Buffer
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Buffer -> Buffer
Gst.Buffer.Buffer) Ptr Buffer
result
    VideoOverlayRectangle -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr VideoOverlayRectangle
rectangle
    Buffer -> IO Buffer
forall (m :: * -> *) a. Monad m => a -> m a
return Buffer
result'

#if defined(ENABLE_OVERLOADING)
data VideoOverlayRectangleGetPixelsUnscaledAyuvMethodInfo
instance (signature ~ ([GstVideo.Flags.VideoOverlayFormatFlags] -> m Gst.Buffer.Buffer), MonadIO m) => O.MethodInfo VideoOverlayRectangleGetPixelsUnscaledAyuvMethodInfo VideoOverlayRectangle signature where
    overloadedMethod = videoOverlayRectangleGetPixelsUnscaledAyuv

#endif

-- method VideoOverlayRectangle::get_pixels_unscaled_raw
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "rectangle"
--           , argType =
--               TInterface
--                 Name { namespace = "GstVideo" , name = "VideoOverlayRectangle" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstVideoOverlayRectangle"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface
--                 Name { namespace = "GstVideo" , name = "VideoOverlayFormatFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "flags.\n   If a global_alpha value != 1 is set for the rectangle, the caller\n   should set the #GST_VIDEO_OVERLAY_FORMAT_FLAG_GLOBAL_ALPHA flag\n   if he wants to apply global-alpha himself. If the flag is not set\n   global_alpha is applied internally before returning the pixel-data."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gst" , name = "Buffer" })
-- throws : False
-- Skip return : False

foreign import ccall "gst_video_overlay_rectangle_get_pixels_unscaled_raw" gst_video_overlay_rectangle_get_pixels_unscaled_raw :: 
    Ptr VideoOverlayRectangle ->            -- rectangle : TInterface (Name {namespace = "GstVideo", name = "VideoOverlayRectangle"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "GstVideo", name = "VideoOverlayFormatFlags"})
    IO (Ptr Gst.Buffer.Buffer)

-- | Retrieves the pixel data as it is. This is useful if the caller can
-- do the scaling itself when handling the overlaying. The rectangle will
-- need to be scaled to the render dimensions, which can be retrieved using
-- 'GI.GstVideo.Structs.VideoOverlayRectangle.videoOverlayRectangleGetRenderRectangle'.
videoOverlayRectangleGetPixelsUnscaledRaw ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VideoOverlayRectangle
    -- ^ /@rectangle@/: a t'GI.GstVideo.Structs.VideoOverlayRectangle.VideoOverlayRectangle'
    -> [GstVideo.Flags.VideoOverlayFormatFlags]
    -- ^ /@flags@/: flags.
    --    If a global_alpha value != 1 is set for the rectangle, the caller
    --    should set the @/GST_VIDEO_OVERLAY_FORMAT_FLAG_GLOBAL_ALPHA/@ flag
    --    if he wants to apply global-alpha himself. If the flag is not set
    --    global_alpha is applied internally before returning the pixel-data.
    -> m Gst.Buffer.Buffer
    -- ^ __Returns:__ a t'GI.Gst.Structs.Buffer.Buffer' holding the pixel data with
    --    t'GI.GstVideo.Structs.VideoMeta.VideoMeta' set. This function does not return a reference, the caller
    --    should obtain a reference of her own with @/gst_buffer_ref()/@ if needed.
videoOverlayRectangleGetPixelsUnscaledRaw :: VideoOverlayRectangle -> [VideoOverlayFormatFlags] -> m Buffer
videoOverlayRectangleGetPixelsUnscaledRaw VideoOverlayRectangle
rectangle [VideoOverlayFormatFlags]
flags = IO Buffer -> m Buffer
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Buffer -> m Buffer) -> IO Buffer -> m Buffer
forall a b. (a -> b) -> a -> b
$ do
    Ptr VideoOverlayRectangle
rectangle' <- VideoOverlayRectangle -> IO (Ptr VideoOverlayRectangle)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr VideoOverlayRectangle
rectangle
    let flags' :: CUInt
flags' = [VideoOverlayFormatFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [VideoOverlayFormatFlags]
flags
    Ptr Buffer
result <- Ptr VideoOverlayRectangle -> CUInt -> IO (Ptr Buffer)
gst_video_overlay_rectangle_get_pixels_unscaled_raw Ptr VideoOverlayRectangle
rectangle' CUInt
flags'
    Text -> Ptr Buffer -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"videoOverlayRectangleGetPixelsUnscaledRaw" Ptr Buffer
result
    Buffer
result' <- ((ManagedPtr Buffer -> Buffer) -> Ptr Buffer -> IO Buffer
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Buffer -> Buffer
Gst.Buffer.Buffer) Ptr Buffer
result
    VideoOverlayRectangle -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr VideoOverlayRectangle
rectangle
    Buffer -> IO Buffer
forall (m :: * -> *) a. Monad m => a -> m a
return Buffer
result'

#if defined(ENABLE_OVERLOADING)
data VideoOverlayRectangleGetPixelsUnscaledRawMethodInfo
instance (signature ~ ([GstVideo.Flags.VideoOverlayFormatFlags] -> m Gst.Buffer.Buffer), MonadIO m) => O.MethodInfo VideoOverlayRectangleGetPixelsUnscaledRawMethodInfo VideoOverlayRectangle signature where
    overloadedMethod = videoOverlayRectangleGetPixelsUnscaledRaw

#endif

-- method VideoOverlayRectangle::get_render_rectangle
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "rectangle"
--           , argType =
--               TInterface
--                 Name { namespace = "GstVideo" , name = "VideoOverlayRectangle" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstVideoOverlayRectangle"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "render_x"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "address where to store the X render offset"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "render_y"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "address where to store the Y render offset"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "render_width"
--           , argType = TBasicType TUInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "address where to store the render width"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "render_height"
--           , argType = TBasicType TUInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "address where to store the render height"
--                 , 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_video_overlay_rectangle_get_render_rectangle" gst_video_overlay_rectangle_get_render_rectangle :: 
    Ptr VideoOverlayRectangle ->            -- rectangle : TInterface (Name {namespace = "GstVideo", name = "VideoOverlayRectangle"})
    Ptr Int32 ->                            -- render_x : TBasicType TInt
    Ptr Int32 ->                            -- render_y : TBasicType TInt
    Ptr Word32 ->                           -- render_width : TBasicType TUInt
    Ptr Word32 ->                           -- render_height : TBasicType TUInt
    IO CInt

-- | Retrieves the render position and render dimension of the overlay
-- rectangle on the video.
videoOverlayRectangleGetRenderRectangle ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VideoOverlayRectangle
    -- ^ /@rectangle@/: a t'GI.GstVideo.Structs.VideoOverlayRectangle.VideoOverlayRectangle'
    -> m ((Bool, Int32, Int32, Word32, Word32))
    -- ^ __Returns:__ TRUE if valid render dimensions were retrieved.
videoOverlayRectangleGetRenderRectangle :: VideoOverlayRectangle -> m (Bool, Int32, Int32, Word32, Word32)
videoOverlayRectangleGetRenderRectangle VideoOverlayRectangle
rectangle = IO (Bool, Int32, Int32, Word32, Word32)
-> m (Bool, Int32, Int32, Word32, Word32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Int32, Int32, Word32, Word32)
 -> m (Bool, Int32, Int32, Word32, Word32))
-> IO (Bool, Int32, Int32, Word32, Word32)
-> m (Bool, Int32, Int32, Word32, Word32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr VideoOverlayRectangle
rectangle' <- VideoOverlayRectangle -> IO (Ptr VideoOverlayRectangle)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr VideoOverlayRectangle
rectangle
    Ptr Int32
renderX <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
renderY <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Word32
renderWidth <- IO (Ptr Word32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word32)
    Ptr Word32
renderHeight <- IO (Ptr Word32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word32)
    CInt
result <- Ptr VideoOverlayRectangle
-> Ptr Int32 -> Ptr Int32 -> Ptr Word32 -> Ptr Word32 -> IO CInt
gst_video_overlay_rectangle_get_render_rectangle Ptr VideoOverlayRectangle
rectangle' Ptr Int32
renderX Ptr Int32
renderY Ptr Word32
renderWidth Ptr Word32
renderHeight
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Int32
renderX' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
renderX
    Int32
renderY' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
renderY
    Word32
renderWidth' <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
renderWidth
    Word32
renderHeight' <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
renderHeight
    VideoOverlayRectangle -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr VideoOverlayRectangle
rectangle
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
renderX
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
renderY
    Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
renderWidth
    Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
renderHeight
    (Bool, Int32, Int32, Word32, Word32)
-> IO (Bool, Int32, Int32, Word32, Word32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Int32
renderX', Int32
renderY', Word32
renderWidth', Word32
renderHeight')

#if defined(ENABLE_OVERLOADING)
data VideoOverlayRectangleGetRenderRectangleMethodInfo
instance (signature ~ (m ((Bool, Int32, Int32, Word32, Word32))), MonadIO m) => O.MethodInfo VideoOverlayRectangleGetRenderRectangleMethodInfo VideoOverlayRectangle signature where
    overloadedMethod = videoOverlayRectangleGetRenderRectangle

#endif

-- method VideoOverlayRectangle::get_seqnum
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "rectangle"
--           , argType =
--               TInterface
--                 Name { namespace = "GstVideo" , name = "VideoOverlayRectangle" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstVideoOverlayRectangle"
--                 , 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_video_overlay_rectangle_get_seqnum" gst_video_overlay_rectangle_get_seqnum :: 
    Ptr VideoOverlayRectangle ->            -- rectangle : TInterface (Name {namespace = "GstVideo", name = "VideoOverlayRectangle"})
    IO Word32

-- | Returns the sequence number of this rectangle. Sequence numbers are
-- monotonically increasing and unique for overlay compositions and rectangles
-- (meaning there will never be a rectangle with the same sequence number as
-- a composition).
-- 
-- Using the sequence number of a rectangle as an indicator for changed
-- pixel-data of a rectangle is dangereous. Some API calls, like e.g.
-- 'GI.GstVideo.Structs.VideoOverlayRectangle.videoOverlayRectangleSetGlobalAlpha', automatically update
-- the per rectangle sequence number, which is misleading for renderers\/
-- consumers, that handle global-alpha themselves. For them  the
-- pixel-data returned by gst_video_overlay_rectangle_get_pixels_*()
-- wont be different for different global-alpha values. In this case a
-- renderer could also use the GstBuffer pointers as a hint for changed
-- pixel-data.
videoOverlayRectangleGetSeqnum ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VideoOverlayRectangle
    -- ^ /@rectangle@/: a t'GI.GstVideo.Structs.VideoOverlayRectangle.VideoOverlayRectangle'
    -> m Word32
    -- ^ __Returns:__ the sequence number of /@rectangle@/
videoOverlayRectangleGetSeqnum :: VideoOverlayRectangle -> m Word32
videoOverlayRectangleGetSeqnum VideoOverlayRectangle
rectangle = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr VideoOverlayRectangle
rectangle' <- VideoOverlayRectangle -> IO (Ptr VideoOverlayRectangle)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr VideoOverlayRectangle
rectangle
    Word32
result <- Ptr VideoOverlayRectangle -> IO Word32
gst_video_overlay_rectangle_get_seqnum Ptr VideoOverlayRectangle
rectangle'
    VideoOverlayRectangle -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr VideoOverlayRectangle
rectangle
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data VideoOverlayRectangleGetSeqnumMethodInfo
instance (signature ~ (m Word32), MonadIO m) => O.MethodInfo VideoOverlayRectangleGetSeqnumMethodInfo VideoOverlayRectangle signature where
    overloadedMethod = videoOverlayRectangleGetSeqnum

#endif

-- method VideoOverlayRectangle::set_global_alpha
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "rectangle"
--           , argType =
--               TInterface
--                 Name { namespace = "GstVideo" , name = "VideoOverlayRectangle" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstVideoOverlayRectangle"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "global_alpha"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Global alpha value (0 to 1.0)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gst_video_overlay_rectangle_set_global_alpha" gst_video_overlay_rectangle_set_global_alpha :: 
    Ptr VideoOverlayRectangle ->            -- rectangle : TInterface (Name {namespace = "GstVideo", name = "VideoOverlayRectangle"})
    CFloat ->                               -- global_alpha : TBasicType TFloat
    IO ()

-- | Sets the global alpha value associated with a t'GI.GstVideo.Structs.VideoOverlayRectangle.VideoOverlayRectangle'. Per-
-- pixel alpha values are multiplied with this value. Valid
-- values: 0 \<= global_alpha \<= 1; 1 to deactivate.
-- 
-- /@rectangle@/ must be writable, meaning its refcount must be 1. You can
-- make the rectangles inside a t'GI.GstVideo.Structs.VideoOverlayComposition.VideoOverlayComposition' writable using
-- 'GI.GstVideo.Structs.VideoOverlayComposition.videoOverlayCompositionMakeWritable' or
-- 'GI.GstVideo.Structs.VideoOverlayComposition.videoOverlayCompositionCopy'.
videoOverlayRectangleSetGlobalAlpha ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VideoOverlayRectangle
    -- ^ /@rectangle@/: a t'GI.GstVideo.Structs.VideoOverlayRectangle.VideoOverlayRectangle'
    -> Float
    -- ^ /@globalAlpha@/: Global alpha value (0 to 1.0)
    -> m ()
videoOverlayRectangleSetGlobalAlpha :: VideoOverlayRectangle -> Float -> m ()
videoOverlayRectangleSetGlobalAlpha VideoOverlayRectangle
rectangle Float
globalAlpha = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr VideoOverlayRectangle
rectangle' <- VideoOverlayRectangle -> IO (Ptr VideoOverlayRectangle)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr VideoOverlayRectangle
rectangle
    let globalAlpha' :: CFloat
globalAlpha' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
globalAlpha
    Ptr VideoOverlayRectangle -> CFloat -> IO ()
gst_video_overlay_rectangle_set_global_alpha Ptr VideoOverlayRectangle
rectangle' CFloat
globalAlpha'
    VideoOverlayRectangle -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr VideoOverlayRectangle
rectangle
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data VideoOverlayRectangleSetGlobalAlphaMethodInfo
instance (signature ~ (Float -> m ()), MonadIO m) => O.MethodInfo VideoOverlayRectangleSetGlobalAlphaMethodInfo VideoOverlayRectangle signature where
    overloadedMethod = videoOverlayRectangleSetGlobalAlpha

#endif

-- method VideoOverlayRectangle::set_render_rectangle
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "rectangle"
--           , argType =
--               TInterface
--                 Name { namespace = "GstVideo" , name = "VideoOverlayRectangle" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GstVideoOverlayRectangle"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "render_x"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "render X position of rectangle on video"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "render_y"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "render Y position of rectangle on video"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "render_width"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "render width of rectangle"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "render_height"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "render height of rectangle"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gst_video_overlay_rectangle_set_render_rectangle" gst_video_overlay_rectangle_set_render_rectangle :: 
    Ptr VideoOverlayRectangle ->            -- rectangle : TInterface (Name {namespace = "GstVideo", name = "VideoOverlayRectangle"})
    Int32 ->                                -- render_x : TBasicType TInt
    Int32 ->                                -- render_y : TBasicType TInt
    Word32 ->                               -- render_width : TBasicType TUInt
    Word32 ->                               -- render_height : TBasicType TUInt
    IO ()

-- | Sets the render position and dimensions of the rectangle on the video.
-- This function is mainly for elements that modify the size of the video
-- in some way (e.g. through scaling or cropping) and need to adjust the
-- details of any overlays to match the operation that changed the size.
-- 
-- /@rectangle@/ must be writable, meaning its refcount must be 1. You can
-- make the rectangles inside a t'GI.GstVideo.Structs.VideoOverlayComposition.VideoOverlayComposition' writable using
-- 'GI.GstVideo.Structs.VideoOverlayComposition.videoOverlayCompositionMakeWritable' or
-- 'GI.GstVideo.Structs.VideoOverlayComposition.videoOverlayCompositionCopy'.
videoOverlayRectangleSetRenderRectangle ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    VideoOverlayRectangle
    -- ^ /@rectangle@/: a t'GI.GstVideo.Structs.VideoOverlayRectangle.VideoOverlayRectangle'
    -> Int32
    -- ^ /@renderX@/: render X position of rectangle on video
    -> Int32
    -- ^ /@renderY@/: render Y position of rectangle on video
    -> Word32
    -- ^ /@renderWidth@/: render width of rectangle
    -> Word32
    -- ^ /@renderHeight@/: render height of rectangle
    -> m ()
videoOverlayRectangleSetRenderRectangle :: VideoOverlayRectangle -> Int32 -> Int32 -> Word32 -> Word32 -> m ()
videoOverlayRectangleSetRenderRectangle VideoOverlayRectangle
rectangle Int32
renderX Int32
renderY Word32
renderWidth Word32
renderHeight = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr VideoOverlayRectangle
rectangle' <- VideoOverlayRectangle -> IO (Ptr VideoOverlayRectangle)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr VideoOverlayRectangle
rectangle
    Ptr VideoOverlayRectangle
-> Int32 -> Int32 -> Word32 -> Word32 -> IO ()
gst_video_overlay_rectangle_set_render_rectangle Ptr VideoOverlayRectangle
rectangle' Int32
renderX Int32
renderY Word32
renderWidth Word32
renderHeight
    VideoOverlayRectangle -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr VideoOverlayRectangle
rectangle
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data VideoOverlayRectangleSetRenderRectangleMethodInfo
instance (signature ~ (Int32 -> Int32 -> Word32 -> Word32 -> m ()), MonadIO m) => O.MethodInfo VideoOverlayRectangleSetRenderRectangleMethodInfo VideoOverlayRectangle signature where
    overloadedMethod = videoOverlayRectangleSetRenderRectangle

#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveVideoOverlayRectangleMethod (t :: Symbol) (o :: *) :: * where
    ResolveVideoOverlayRectangleMethod "copy" o = VideoOverlayRectangleCopyMethodInfo
    ResolveVideoOverlayRectangleMethod "getFlags" o = VideoOverlayRectangleGetFlagsMethodInfo
    ResolveVideoOverlayRectangleMethod "getGlobalAlpha" o = VideoOverlayRectangleGetGlobalAlphaMethodInfo
    ResolveVideoOverlayRectangleMethod "getPixelsArgb" o = VideoOverlayRectangleGetPixelsArgbMethodInfo
    ResolveVideoOverlayRectangleMethod "getPixelsAyuv" o = VideoOverlayRectangleGetPixelsAyuvMethodInfo
    ResolveVideoOverlayRectangleMethod "getPixelsRaw" o = VideoOverlayRectangleGetPixelsRawMethodInfo
    ResolveVideoOverlayRectangleMethod "getPixelsUnscaledArgb" o = VideoOverlayRectangleGetPixelsUnscaledArgbMethodInfo
    ResolveVideoOverlayRectangleMethod "getPixelsUnscaledAyuv" o = VideoOverlayRectangleGetPixelsUnscaledAyuvMethodInfo
    ResolveVideoOverlayRectangleMethod "getPixelsUnscaledRaw" o = VideoOverlayRectangleGetPixelsUnscaledRawMethodInfo
    ResolveVideoOverlayRectangleMethod "getRenderRectangle" o = VideoOverlayRectangleGetRenderRectangleMethodInfo
    ResolveVideoOverlayRectangleMethod "getSeqnum" o = VideoOverlayRectangleGetSeqnumMethodInfo
    ResolveVideoOverlayRectangleMethod "setGlobalAlpha" o = VideoOverlayRectangleSetGlobalAlphaMethodInfo
    ResolveVideoOverlayRectangleMethod "setRenderRectangle" o = VideoOverlayRectangleSetRenderRectangleMethodInfo
    ResolveVideoOverlayRectangleMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveVideoOverlayRectangleMethod t VideoOverlayRectangle, O.MethodInfo info VideoOverlayRectangle p) => OL.IsLabel t (VideoOverlayRectangle -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif